Arithmetic derivative

The arithmetic derivative of an integer (more specifically, the Lagarias arithmetic derivative) is a function defined for integers, based on prime factorization, by analogy with the product rule for the derivative of a function that is used in mathematical analysis. Accordingly, for natural numbers n, the arithmetic derivative D(n) is defined as follows:

Task
Arithmetic derivative
You are encouraged to solve this task according to the task description, using any language you may know.
  • .
  • .
  • . (Leibniz rule for derivatives).

Additionally, for negative integers the arithmetic derivative may be defined as .

Examples

and (both are prime) so if , then .

.

Task

Find and show the arithmetic derivatives for -99 through 100.

Stretch task

Find (the arithmetic derivative of ) then divided by 7, where m is from 1 to 20.

See also

ABC

HOW TO RETURN lagarias n:
    SELECT:
        n<0: RETURN -lagarias -n
        n in {0;1}: RETURN 0
        NO d IN {2..floor root n} HAS n mod d=0: RETURN 1
        ELSE: RETURN ((n/d) * lagarias d) + (d * lagarias (n/d))

PUT 0 IN col
FOR n IN {-99..100}:
    WRITE (lagarias n)>>6
    PUT col+1 IN col
    IF col mod 10 = 0: WRITE/

FOR m IN {1..20}:
    WRITE "D(10^`m>>2`) = `(lagarias (10**m))/7`"/
Output:
   -75   -77    -1  -272   -24   -49   -34   -96   -20  -123
    -1  -140   -32   -45   -22  -124    -1   -43  -108  -176
    -1   -71   -18   -80   -55   -39    -1  -156    -1   -59
   -26   -72    -1   -61   -18  -192   -51   -33    -1   -92
    -1   -31   -22   -92   -16   -81    -1   -56   -20   -45
   -14  -112    -1   -25   -39   -48    -1   -41    -1   -68
   -16   -21    -1   -60   -12   -19   -14   -80    -1   -31
    -1   -32   -27   -15   -10   -44    -1   -13   -10   -24
    -1   -21    -1   -32    -8    -9    -1   -16    -1    -7
    -6   -12    -1    -5    -1    -4    -1    -1     0     0
     0     1     1     4     1     5     1    12     6     7
     1    16     1     9     8    32     1    21     1    24
    10    13     1    44    10    15    27    32     1    31
     1    80    14    19    12    60     1    21    16    68
     1    41     1    48    39    25     1   112    14    45
    20    56     1    81    16    92    22    31     1    92
     1    33    51   192    18    61     1    72    26    59
     1   156     1    39    55    80    18    71     1   176
   108    43     1   124    22    45    32   140     1   123
    20    96    34    49    24   272     1    77    75   140
D(10^ 1) = 1
D(10^ 2) = 20
D(10^ 3) = 300
D(10^ 4) = 4000
D(10^ 5) = 50000
D(10^ 6) = 600000
D(10^ 7) = 7000000
D(10^ 8) = 80000000
D(10^ 9) = 900000000
D(10^10) = 10000000000
D(10^11) = 110000000000
D(10^12) = 1200000000000
D(10^13) = 13000000000000
D(10^14) = 140000000000000
D(10^15) = 1500000000000000
D(10^16) = 16000000000000000
D(10^17) = 170000000000000000
D(10^18) = 1800000000000000000
D(10^19) = 19000000000000000000
D(10^20) = 200000000000000000000

Action!

Translation of: BASIC
PROC Main()
  INT n, f, l, z
  FOR n = -99 TO 100 DO
    l = 0  f = 3  IF n < 0 THEN z = - n ELSE z = n FI
    WHILE z >= 2 DO
      WHILE z MOD 2 = 0 DO l ==+ n / 2     z ==/ 2 OD
      IF f <= z THEN
        WHILE z MOD f = 0 DO l ==+ n / f   z ==/ f OD
        f ==+ 2
      FI
    OD
    PrintF( "%8I", l )  
    IF ( n + 100 ) MOD 10 = 0 THEN PutE() FI
  OD
RETURN
Output:
     -75     -77      -1    -272     -24     -49     -34     -96     -20    -123
      -1    -140     -32     -45     -22    -124      -1     -43    -108    -176
      -1     -71     -18     -80     -55     -39      -1    -156      -1     -59
     -26     -72      -1     -61     -18    -192     -51     -33      -1     -92
      -1     -31     -22     -92     -16     -81      -1     -56     -20     -45
     -14    -112      -1     -25     -39     -48      -1     -41      -1     -68
     -16     -21      -1     -60     -12     -19     -14     -80      -1     -31
      -1     -32     -27     -15     -10     -44      -1     -13     -10     -24
      -1     -21      -1     -32      -8      -9      -1     -16      -1      -7
      -6     -12      -1      -5      -1      -4      -1      -1       0       0
       0       1       1       4       1       5       1      12       6       7
       1      16       1       9       8      32       1      21       1      24
      10      13       1      44      10      15      27      32       1      31
       1      80      14      19      12      60       1      21      16      68
       1      41       1      48      39      25       1     112      14      45
      20      56       1      81      16      92      22      31       1      92
       1      33      51     192      18      61       1      72      26      59
       1     156       1      39      55      80      18      71       1     176
     108      43       1     124      22      45      32     140       1     123
      20      96      34      49      24     272       1      77      75     140

Ada

with Ada.Text_IO; use Ada.Text_IO;
with Ada.Integer_Text_IO; use Ada.Integer_Text_IO;
with Ada.Numerics.Big_Numbers.Big_Integers; use Ada.Numerics.Big_Numbers.Big_Integers;

procedure Arithmetic_Derivative is

	function D (N : Big_Integer) return Big_Integer is
		Inc : Constant array (1 .. 8) of Big_Integer := (4, 2, 4, 2, 4, 6, 2, 6);
		I : Integer := 1;
		Num : Big_Integer := N;
		P : Big_Integer := 2;
		PCount : Big_Integer;
		Result : Big_Integer := 0;
	begin
		if N < 0 then return -D(-N); end if;
		if N = 0 or N = 1 then return 0; end if;

		while P <= N / 2 loop
			if Num mod P = 0 then
				PCount := 0;
				while Num mod P = 0 loop
					Num := Num / P;
					PCount := PCount + 1;
				end loop;
				Result := Result + (PCount * N) / P;
			end if;
			if Num = 1 then exit; end if;
			if P >= 7 then
				P := P + Inc(I);
				I := (I mod 8) + 1;
			end if;
			if P = 3 or P = 5 then P := P + 2; end if;
			if P = 2 then P := P + 1; end if;
		end loop;
		
		if Num > 1 then return 1; end if;

		return result;
	end D;

	P : Big_Integer;

begin
	for I in Integer range -99 .. 100 loop
		P := To_Big_Integer(I);
		Put(To_String(Arg => D(P), Width => 5));
		if I mod 10 = 0 then New_Line; end if;
	end loop;

	for I in Integer range 1 .. 20 loop
		P := 10 ** I;
		Put("D(10^"); Put(Item => I, Width => 2); Put(") / 7 = ");
		Put(Big_Integer'Image(D(P) / 7)); New_Line;
	end loop;
end Arithmetic_Derivative;
Output:
  -75  -77   -1 -272  -24  -49  -34  -96  -20 -123
   -1 -140  -32  -45  -22 -124   -1  -43 -108 -176
   -1  -71  -18  -80  -55  -39   -1 -156   -1  -59
  -26  -72   -1  -61  -18 -192  -51  -33   -1  -92
   -1  -31  -22  -92  -16  -81   -1  -56  -20  -45
  -14 -112   -1  -25  -39  -48   -1  -41   -1  -68
  -16  -21   -1  -60  -12  -19  -14  -80   -1  -31
   -1  -32  -27  -15  -10  -44   -1  -13  -10  -24
   -1  -21   -1  -32   -8   -9   -1  -16   -1   -7
   -6  -12   -1   -5   -1   -4   -1   -1    0    0
    0    1    1    4    1    5    1   12    6    7
    1   16    1    9    8   32    1   21    1   24
   10   13    1   44   10   15   27   32    1   31
    1   80   14   19   12   60    1   21   16   68
    1   41    1   48   39   25    1  112   14   45
   20   56    1   81   16   92   22   31    1   92
    1   33   51  192   18   61    1   72   26   59
    1  156    1   39   55   80   18   71    1  176
  108   43    1  124   22   45   32  140    1  123
   20   96   34   49   24  272    1   77   75  140
D(10^ 1) / 7 =  1
D(10^ 2) / 7 =  20
D(10^ 3) / 7 =  300
D(10^ 4) / 7 =  4000
D(10^ 5) / 7 =  50000
D(10^ 6) / 7 =  600000
D(10^ 7) / 7 =  7000000
D(10^ 8) / 7 =  80000000
D(10^ 9) / 7 =  900000000
D(10^10) / 7 =  10000000000
D(10^11) / 7 =  110000000000
D(10^12) / 7 =  1200000000000
D(10^13) / 7 =  13000000000000
D(10^14) / 7 =  140000000000000
D(10^15) / 7 =  1500000000000000
D(10^16) / 7 =  16000000000000000
D(10^17) / 7 =  170000000000000000
D(10^18) / 7 =  1800000000000000000
D(10^19) / 7 =  19000000000000000000
D(10^20) / 7 =  200000000000000000000

ALGOL 68

Recursive

BEGIN PROC lagarias = (LONG INT n) LONG INT: # Lagarias arithmetic derivative #
           IF n < 0
           THEN -lagarias (-n)
           ELIF n = 0 OR n = 1
           THEN 0
           ELIF PROC small pf = (LONG INT j, k) LONG INT: # Smallest prime factor #
                     (j %* k = 0 | k | small pf (j, k + 1));
                LONG INT f = small pf (n, 2); LONG INT q = n % f; 
                q = 1
           THEN 1
           ELSE q * lagarias (f) + f * lagarias (q)
           FI;

      FOR n FROM -99 TO 100
      DO print (("D(", whole (n, 0), ") = ", whole (lagarias (n), 0), new line))
      OD;
      new line (standout);
      FOR n TO 20
      DO LONG INT m = LONG 10 ^ n;
         print (("D(", whole (m, 0), ") / 7 = ", whole (lagarias (m) % 7, 0), new line))
      OD
END
Output:
D(-99) = -75
D(-98) = -77
D(-97) = -1
D(-96) = -272
...
D(96) = 272
D(97) = 1
D(98) = 77
D(99) = 75
D(100) = 140
D(10) / 7 = 1
D(100) / 7 = 20
D(1000) / 7 = 300
...
D(1000000000000000000) / 7 = 1800000000000000000
D(10000000000000000000) / 7 = 19000000000000000000
D(100000000000000000000) / 7 = 200000000000000000000

Iterative

Translation of: BASIC – via Action!
FOR n FROM -99 TO 100 DO
    INT l := 0, f := 3, z := ABS n;
    WHILE z >= 2 DO
        WHILE z MOD 2 = 0 DO     l +:= n OVER 2; z OVERAB 2 OD;
        IF f <= z THEN
            WHILE z MOD f = 0 DO l +:= n OVER f; z OVERAB f OD;
            f +:= 2
        FI
    OD;
    print( ( whole( l, -8 ) ) ); 
    IF ( n + 100 ) MOD 10 = 0 THEN print( ( newline ) ) FI
OD
Output:

Same as the Action! sample.

ALGOL W

Translation of: ALGOL 68 – using compressed output and basic task only as Algol W integers are limited to 32 bits
begin
   integer procedure lagarias ( integer value n ) ; % Lagarias arithmetic derivative %
           if n < 0
           then -lagarias (-n)
           else if n = 0 or n = 1
           then 0
           else begin
                integer f, q;
                integer procedure smallPf ( integer value j, k ) ; % Smallest prime factor %
                    if j rem k = 0 then k else smallPf (j, k + 1);
                f := smallPf (n, 2); q := n div f; 
                if q = 1
                then 1
                else q * lagarias (f) + f * lagarias (q)
           end lagarias ;

   for n := -99 until 100 do begin
       writeon( i_w := 6, s_w := 0, " ", lagarias (n) );
       if n rem 10 = 0 then write()
   end for_n
end.
Output:
    -75    -77     -1   -272    -24    -49    -34    -96    -20   -123
     -1   -140    -32    -45    -22   -124     -1    -43   -108   -176
     -1    -71    -18    -80    -55    -39     -1   -156     -1    -59
    -26    -72     -1    -61    -18   -192    -51    -33     -1    -92
     -1    -31    -22    -92    -16    -81     -1    -56    -20    -45
    -14   -112     -1    -25    -39    -48     -1    -41     -1    -68
    -16    -21     -1    -60    -12    -19    -14    -80     -1    -31
     -1    -32    -27    -15    -10    -44     -1    -13    -10    -24
     -1    -21     -1    -32     -8     -9     -1    -16     -1     -7
     -6    -12     -1     -5     -1     -4     -1     -1      0      0
      0      1      1      4      1      5      1     12      6      7
      1     16      1      9      8     32      1     21      1     24
     10     13      1     44     10     15     27     32      1     31
      1     80     14     19     12     60      1     21     16     68
      1     41      1     48     39     25      1    112     14     45
     20     56      1     81     16     92     22     31      1     92
      1     33     51    192     18     61      1     72     26     59
      1    156      1     39     55     80     18     71      1    176
    108     43      1    124     22     45     32    140      1    123
     20     96     34     49     24    272      1     77     75    140

APL

Works with: Dyalog APL
lagarias{
   <0:--
   0 1:0
   0=d1+⍸0=(1↓⍳⌊2)|⍵:1
   (n×d)+d×n÷d
}
lagarias¨ 20 10¯100+⍳200
Output:
¯75  ¯77  ¯1 ¯272 ¯24  ¯49 ¯34  ¯96  ¯20 ¯123
 ¯1 ¯140 ¯32  ¯45 ¯22 ¯124  ¯1  ¯43 ¯108 ¯176
 ¯1  ¯71 ¯18  ¯80 ¯55  ¯39  ¯1 ¯156   ¯1  ¯59
¯26  ¯72  ¯1  ¯61 ¯18 ¯192 ¯51  ¯33   ¯1  ¯92
 ¯1  ¯31 ¯22  ¯92 ¯16  ¯81  ¯1  ¯56  ¯20  ¯45
¯14 ¯112  ¯1  ¯25 ¯39  ¯48  ¯1  ¯41   ¯1  ¯68
¯16  ¯21  ¯1  ¯60 ¯12  ¯19 ¯14  ¯80   ¯1  ¯31
 ¯1  ¯32 ¯27  ¯15 ¯10  ¯44  ¯1  ¯13  ¯10  ¯24
 ¯1  ¯21  ¯1  ¯32  ¯8   ¯9  ¯1  ¯16   ¯1   ¯7
 ¯6  ¯12  ¯1   ¯5  ¯1   ¯4  ¯1   ¯1    0    0
  0    1   1    4   1    5   1   12    6    7
  1   16   1    9   8   32   1   21    1   24
 10   13   1   44  10   15  27   32    1   31
  1   80  14   19  12   60   1   21   16   68
  1   41   1   48  39   25   1  112   14   45
 20   56   1   81  16   92  22   31    1   92
  1   33  51  192  18   61   1   72   26   59
  1  156   1   39  55   80  18   71    1  176
108   43   1  124  22   45  32  140    1  123
 20   96  34   49  24  272   1   77   75  140


Arturo

D: $[x][
    when [
        x < 0 -> neg D neg x
        x = 0 -> 0
        x = 1 -> 0
        prime? x -> 1
        any [
            m: 2
            while [0 <> x % m] -> inc 'm
            n: x / m
            (n * D m) + m * D n
        ]
    ]
]

(neg 99)..100 | map => D
              | split.every:10
              | loop => [loop & 'n -> prints pad to :string n 5 print ""]
print ""
loop 20 'n -> print ~"D(10^|n|)/7 = |div D 10^n 7|"
Output:
  -75  -77   -1 -272  -24  -49  -34  -96  -20 -123
   -1 -140  -32  -45  -22 -124   -1  -43 -108 -176
   -1  -71  -18  -80  -55  -39   -1 -156   -1  -59
  -26  -72   -1  -61  -18 -192  -51  -33   -1  -92
   -1  -31  -22  -92  -16  -81   -1  -56  -20  -45
  -14 -112   -1  -25  -39  -48   -1  -41   -1  -68
  -16  -21   -1  -60  -12  -19  -14  -80   -1  -31
   -1  -32  -27  -15  -10  -44   -1  -13  -10  -24
   -1  -21   -1  -32   -8   -9   -1  -16   -1   -7
   -6  -12   -1   -5   -1   -4   -1   -1    0    0
    0    1    1    4    1    5    1   12    6    7
    1   16    1    9    8   32    1   21    1   24
   10   13    1   44   10   15   27   32    1   31
    1   80   14   19   12   60    1   21   16   68
    1   41    1   48   39   25    1  112   14   45
   20   56    1   81   16   92   22   31    1   92
    1   33   51  192   18   61    1   72   26   59
    1  156    1   39   55   80   18   71    1  176
  108   43    1  124   22   45   32  140    1  123
   20   96   34   49   24  272    1   77   75  140

D(10^1)/7 = 1
D(10^2)/7 = 20
D(10^3)/7 = 300
D(10^4)/7 = 4000
D(10^5)/7 = 50000
D(10^6)/7 = 600000
D(10^7)/7 = 7000000
D(10^8)/7 = 80000000
D(10^9)/7 = 900000000
D(10^10)/7 = 10000000000
D(10^11)/7 = 110000000000
D(10^12)/7 = 1200000000000
D(10^13)/7 = 13000000000000
D(10^14)/7 = 140000000000000
D(10^15)/7 = 1500000000000000
D(10^16)/7 = 16000000000000000
D(10^17)/7 = 170000000000000000
D(10^18)/7 = 1800000000000000000
D(10^19)/7 = 19000000000000000000
D(10^20)/7 = 200000000000000000000

BASIC

10 DEFINT A-Z
20 FOR N=-99 TO 100
30 GOSUB 100: PRINT USING "########";L;
40 NEXT
50 END
100 L=0: F=3: Z=ABS(N)
110 IF Z<2 THEN RETURN
120 IF Z MOD 2=0 THEN L=L+N\2: Z=Z\2: GOTO 120
130 IF F>Z THEN RETURN
140 IF Z MOD F=0 THEN L=L+N\F: Z=Z\F: GOTO 140
150 F=F+2
160 GOTO 130
Output:
     -75     -77      -1    -272     -24     -49     -34     -96     -20    -123
      -1    -140     -32     -45     -22    -124      -1     -43    -108    -176
      -1     -71     -18     -80     -55     -39      -1    -156      -1     -59
     -26     -72      -1     -61     -18    -192     -51     -33      -1     -92
      -1     -31     -22     -92     -16     -81      -1     -56     -20     -45
     -14    -112      -1     -25     -39     -48      -1     -41      -1     -68
     -16     -21      -1     -60     -12     -19     -14     -80      -1     -31
      -1     -32     -27     -15     -10     -44      -1     -13     -10     -24
      -1     -21      -1     -32      -8      -9      -1     -16      -1      -7
      -6     -12      -1      -5      -1      -4      -1      -1       0       0
       0       1       1       4       1       5       1      12       6       7
       1      16       1       9       8      32       1      21       1      24
      10      13       1      44      10      15      27      32       1      31
       1      80      14      19      12      60       1      21      16      68
       1      41       1      48      39      25       1     112      14      45
      20      56       1      81      16      92      22      31       1      92
       1      33      51     192      18      61       1      72      26      59
       1     156       1      39      55      80      18      71       1     176
     108      43       1     124      22      45      32     140       1     123
      20      96      34      49      24     272       1      77      75     140

C

Translation of: Go
#include <stdio.h>
#include <stdint.h>

typedef uint64_t u64;

void primeFactors(u64 n, u64 *factors, int *length) {
    if (n < 2) return;
    int count = 0;
    int inc[8] = {4, 2, 4, 2, 4, 6, 2, 6};
    while (!(n%2)) {
        factors[count++] = 2;
        n /= 2;
    }
    while (!(n%3)) {
        factors[count++] = 3;
        n /= 3;
    }
    while (!(n%5)) {
        factors[count++] = 5;
        n /= 5;
    }
    for (u64 k = 7, i = 0; k*k <= n; ) {
        if (!(n%k)) {
            factors[count++] = k;
            n /= k;
        } else {
            k += inc[i];
            i = (i + 1) % 8;
        }
    }
    if (n > 1) {
        factors[count++] = n;
    }
    *length = count;
}

double D(double n) {
    if (n < 0) return -D(-n);
    if (n < 2) return 0;
    int i, length;
    double d;
    u64 f[80], g;
    if (n < 1e19) {
        primeFactors((u64)n, f, &length);
    } else {
        g = (u64)(n / 100);
        primeFactors(g, f, &length);
        f[length+1] = f[length] = 2;
        f[length+3] = f[length+2] = 5;
        length += 4;
    }
    if (length == 1) return 1;
    if (length == 2) return (double)(f[0] + f[1]);
    d = n / (double)f[0];
    return D(d) * (double)f[0] + d;
}

int main() {
    u64 ad[200];
    int n, m;
    double pow;
    for (n = -99; n < 101; ++n) {
        ad[n+99] = (int)D((double)n);
    }
    for (n = 0; n < 200; ++n) {
        printf("%4ld ", ad[n]);
        if (!((n+1)%10)) printf("\n");
    }
    printf("\n");
    pow = 1;
    for (m = 1; m < 21; ++m) {
        pow *= 10;
        printf("D(10^%-2d) / 7 = %.0f\n", m, D(pow)/7);
    }
    return 0;
}
Output:
As Go example

C++

Library: Boost
#include <iomanip>
#include <iostream>

#include <boost/multiprecision/cpp_int.hpp>

template <typename IntegerType>
IntegerType arithmetic_derivative(IntegerType n) {
    bool negative = n < 0;
    if (negative)
        n = -n;
    if (n < 2)
        return 0;
    IntegerType sum = 0, count = 0, m = n;
    while ((m & 1) == 0) {
        m >>= 1;
        count += n;
    }
    if (count > 0)
        sum += count / 2;
    for (IntegerType p = 3, sq = 9; sq <= m; p += 2) {
        count = 0;
        while (m % p == 0) {
            m /= p;
            count += n;
        }
        if (count > 0)
            sum += count / p;
        sq += (p + 1) << 2;
    }
    if (m > 1)
        sum += n / m;
    if (negative)
        sum = -sum;
    return sum;
}

int main() {
    using boost::multiprecision::int128_t;

    for (int n = -99, i = 0; n <= 100; ++n, ++i) {
        std::cout << std::setw(4) << arithmetic_derivative(n)
                  << ((i + 1) % 10 == 0 ? '\n' : ' ');
    }

    int128_t p = 10;
    std::cout << '\n';
    for (int i = 0; i < 20; ++i, p *= 10) {
        std::cout << "D(10^" << std::setw(2) << i + 1
                  << ") / 7 = " << arithmetic_derivative(p) / 7 << '\n';
    }
}
Output:
 -75  -77   -1 -272  -24  -49  -34  -96  -20 -123
  -1 -140  -32  -45  -22 -124   -1  -43 -108 -176
  -1  -71  -18  -80  -55  -39   -1 -156   -1  -59
 -26  -72   -1  -61  -18 -192  -51  -33   -1  -92
  -1  -31  -22  -92  -16  -81   -1  -56  -20  -45
 -14 -112   -1  -25  -39  -48   -1  -41   -1  -68
 -16  -21   -1  -60  -12  -19  -14  -80   -1  -31
  -1  -32  -27  -15  -10  -44   -1  -13  -10  -24
  -1  -21   -1  -32   -8   -9   -1  -16   -1   -7
  -6  -12   -1   -5   -1   -4   -1   -1    0    0
   0    1    1    4    1    5    1   12    6    7
   1   16    1    9    8   32    1   21    1   24
  10   13    1   44   10   15   27   32    1   31
   1   80   14   19   12   60    1   21   16   68
   1   41    1   48   39   25    1  112   14   45
  20   56    1   81   16   92   22   31    1   92
   1   33   51  192   18   61    1   72   26   59
   1  156    1   39   55   80   18   71    1  176
 108   43    1  124   22   45   32  140    1  123
  20   96   34   49   24  272    1   77   75  140

D(10^ 1) / 7 = 1
D(10^ 2) / 7 = 20
D(10^ 3) / 7 = 300
D(10^ 4) / 7 = 4000
D(10^ 5) / 7 = 50000
D(10^ 6) / 7 = 600000
D(10^ 7) / 7 = 7000000
D(10^ 8) / 7 = 80000000
D(10^ 9) / 7 = 900000000
D(10^10) / 7 = 10000000000
D(10^11) / 7 = 110000000000
D(10^12) / 7 = 1200000000000
D(10^13) / 7 = 13000000000000
D(10^14) / 7 = 140000000000000
D(10^15) / 7 = 1500000000000000
D(10^16) / 7 = 16000000000000000
D(10^17) / 7 = 170000000000000000
D(10^18) / 7 = 1800000000000000000
D(10^19) / 7 = 19000000000000000000
D(10^20) / 7 = 200000000000000000000

CLU

factors = iter (n: bigint) yields (bigint)
    own zero: bigint := bigint$i2bi(0)
    own two: bigint := bigint$i2bi(2)
    own three: bigint := bigint$i2bi(3)

    while n>zero cand n//two = zero do yield(two) n := n/two end

    fac: bigint := three
    while fac<=n do
        while n//fac = zero do yield(fac) n := n/fac end
        fac := fac + two
    end
end factors

lagarias = proc (n: bigint) returns (bigint)
    own zero: bigint := bigint$i2bi(0)
    if n < zero then return(-lagarias(-n)) end

    sum: bigint := zero
    for fac: bigint in factors(n) do
        sum := sum + n / fac
    end
    return(sum)
end lagarias

start_up = proc ()
    own po: stream := stream$primary_output()
    own seven: bigint := bigint$i2bi(7)
    own ten: bigint := bigint$i2bi(10)

    for n: int in int$from_to(-99, 100) do
        stream$putright(po, bigint$unparse(lagarias(bigint$i2bi(n))), 7)
        if (n + 100)//10 = 0 then stream$putl(po, "") end
    end

    for m: int in int$from_to(1, 20) do
        d: bigint := lagarias(ten ** bigint$i2bi(m)) / seven
        stream$puts(po, "D(10^")
        stream$putright(po, int$unparse(m), 2)
        stream$puts(po, ") / 7 = ")
        stream$putright(po, bigint$unparse(d), 25)
        stream$putl(po, "")
    end
end start_up
Output:
    -75    -77     -1   -272    -24    -49    -34    -96    -20   -123
     -1   -140    -32    -45    -22   -124     -1    -43   -108   -176
     -1    -71    -18    -80    -55    -39     -1   -156     -1    -59
    -26    -72     -1    -61    -18   -192    -51    -33     -1    -92
     -1    -31    -22    -92    -16    -81     -1    -56    -20    -45
    -14   -112     -1    -25    -39    -48     -1    -41     -1    -68
    -16    -21     -1    -60    -12    -19    -14    -80     -1    -31
     -1    -32    -27    -15    -10    -44     -1    -13    -10    -24
     -1    -21     -1    -32     -8     -9     -1    -16     -1     -7
     -6    -12     -1     -5     -1     -4     -1     -1      0      0
      0      1      1      4      1      5      1     12      6      7
      1     16      1      9      8     32      1     21      1     24
     10     13      1     44     10     15     27     32      1     31
      1     80     14     19     12     60      1     21     16     68
      1     41      1     48     39     25      1    112     14     45
     20     56      1     81     16     92     22     31      1     92
      1     33     51    192     18     61      1     72     26     59
      1    156      1     39     55     80     18     71      1    176
    108     43      1    124     22     45     32    140      1    123
     20     96     34     49     24    272      1     77     75    140
D(10^ 1) / 7 =                         1
D(10^ 2) / 7 =                        20
D(10^ 3) / 7 =                       300
D(10^ 4) / 7 =                      4000
D(10^ 5) / 7 =                     50000
D(10^ 6) / 7 =                    600000
D(10^ 7) / 7 =                   7000000
D(10^ 8) / 7 =                  80000000
D(10^ 9) / 7 =                 900000000
D(10^10) / 7 =               10000000000
D(10^11) / 7 =              110000000000
D(10^12) / 7 =             1200000000000
D(10^13) / 7 =            13000000000000
D(10^14) / 7 =           140000000000000
D(10^15) / 7 =          1500000000000000
D(10^16) / 7 =         16000000000000000
D(10^17) / 7 =        170000000000000000
D(10^18) / 7 =       1800000000000000000
D(10^19) / 7 =      19000000000000000000
D(10^20) / 7 =     200000000000000000000

Cowgol

include "cowgol.coh";

sub abs(n: int32): (r: uint32) is
    if n<0 then
        r := (-n) as uint32;
    else
        r := n as uint32;
    end if;
end sub;

sub printcol(n: int32, s: uint8) is
    var buf: uint8[12];
    var ptr := IToA(n, 10, &buf[0]);
    s := s - (ptr - &buf[0]) as uint8;
    while s>0 loop
        print_char(' ');
        s := s-1;
    end loop;
    print(&buf[0]);
end sub;

sub lagarias(n: int32): (r: int32) is
    var nn := abs(n);
    r := 0;
    if nn<2 then return; end if;
    var f: uint32 := 2;
    while f<=nn loop
        while nn%f == 0 loop
            r := r + n/f as int32;
            nn := nn/f;
        end loop;
        f := f+1;
    end loop;
end sub;

var i: int32 := -99;
var c: uint8 := 0;
while i <= 100 loop
    printcol(lagarias(i), 7);
    i := i+1;
    c := c+1;
    if c%10 == 0 then print_nl(); end if;
end loop;
Output:
    -75    -77     -1   -272    -24    -49    -34    -96    -20   -123
     -1   -140    -32    -45    -22   -124     -1    -43   -108   -176
     -1    -71    -18    -80    -55    -39     -1   -156     -1    -59
    -26    -72     -1    -61    -18   -192    -51    -33     -1    -92
     -1    -31    -22    -92    -16    -81     -1    -56    -20    -45
    -14   -112     -1    -25    -39    -48     -1    -41     -1    -68
    -16    -21     -1    -60    -12    -19    -14    -80     -1    -31
     -1    -32    -27    -15    -10    -44     -1    -13    -10    -24
     -1    -21     -1    -32     -8     -9     -1    -16     -1     -7
     -6    -12     -1     -5     -1     -4     -1     -1      0      0
      0      1      1      4      1      5      1     12      6      7
      1     16      1      9      8     32      1     21      1     24
     10     13      1     44     10     15     27     32      1     31
      1     80     14     19     12     60      1     21     16     68
      1     41      1     48     39     25      1    112     14     45
     20     56      1     81     16     92     22     31      1     92
      1     33     51    192     18     61      1     72     26     59
      1    156      1     39     55     80     18     71      1    176
    108     43      1    124     22     45     32    140      1    123
     20     96     34     49     24    272      1     77     75    140

Draco

proc lagarias(int n) int:
    int f, r, s;
    if n<0 then
        -lagarias(-n)
    elif n<2 then
        0
    else
        s := 0;
        r := n;
        while r % 2 = 0 do
            r := r / 2;
            s := s + n / 2
        od;
        f := 3;
        while f <= r do
            while r % f = 0 do
                r := r / f;
                s := s + n / f
            od;
            f := f + 2
        od;
        s
    fi
corp

proc main() void:
    int n;
    for n from -99 upto 100 do
        write(lagarias(n):7);
        if (n+100) % 10=0 then writeln() fi
    od
corp
Output:
    -75    -77     -1   -272    -24    -49    -34    -96    -20   -123
     -1   -140    -32    -45    -22   -124     -1    -43   -108   -176
     -1    -71    -18    -80    -55    -39     -1   -156     -1    -59
    -26    -72     -1    -61    -18   -192    -51    -33     -1    -92
     -1    -31    -22    -92    -16    -81     -1    -56    -20    -45
    -14   -112     -1    -25    -39    -48     -1    -41     -1    -68
    -16    -21     -1    -60    -12    -19    -14    -80     -1    -31
     -1    -32    -27    -15    -10    -44     -1    -13    -10    -24
     -1    -21     -1    -32     -8     -9     -1    -16     -1     -7
     -6    -12     -1     -5     -1     -4     -1     -1      0      0
      0      1      1      4      1      5      1     12      6      7
      1     16      1      9      8     32      1     21      1     24
     10     13      1     44     10     15     27     32      1     31
      1     80     14     19     12     60      1     21     16     68
      1     41      1     48     39     25      1    112     14     45
     20     56      1     81     16     92     22     31      1     92
      1     33     51    192     18     61      1     72     26     59
      1    156      1     39     55     80     18     71      1    176
    108     43      1    124     22     45     32    140      1    123
     20     96     34     49     24    272      1     77     75    140

EasyLang

Translation of: Lua
func lagarias n .
   if n < 0
      return -lagarias -n
   .
   if n = 0 or n = 1
      return 0
   .
   f = 2
   while n mod f <> 0
      f += 1
   .
   q = n / f
   if q = 1
      return 1
   .
   return q * lagarias f + f * lagarias q
.
for n = -99 to 100
   write lagarias n & " "
.

Factor

Works with: Factor version 0.99 2022-04-03
USING: combinators formatting grouping io kernel math
math.primes.factors prettyprint ranges sequences ;

: n' ( m -- n )
    {
        { [ dup neg? ] [ neg n' neg ] }
        { [ dup 2 < ] [ drop 0 ] }
        { [ factors dup length 1 = ] [ drop 1 ] }
        [ unclip-slice swap product 2dup n' * spin n' * + ]
    } cond ;

-99 100 [a..b] [ n' ] map 10 group
[ [ "%5d" printf ] each nl ] each
Output:
  -75  -77   -1 -272  -24  -49  -34  -96  -20 -123
   -1 -140  -32  -45  -22 -124   -1  -43 -108 -176
   -1  -71  -18  -80  -55  -39   -1 -156   -1  -59
  -26  -72   -1  -61  -18 -192  -51  -33   -1  -92
   -1  -31  -22  -92  -16  -81   -1  -56  -20  -45
  -14 -112   -1  -25  -39  -48   -1  -41   -1  -68
  -16  -21   -1  -60  -12  -19  -14  -80   -1  -31
   -1  -32  -27  -15  -10  -44   -1  -13  -10  -24
   -1  -21   -1  -32   -8   -9   -1  -16   -1   -7
   -6  -12   -1   -5   -1   -4   -1   -1    0    0
    0    1    1    4    1    5    1   12    6    7
    1   16    1    9    8   32    1   21    1   24
   10   13    1   44   10   15   27   32    1   31
    1   80   14   19   12   60    1   21   16   68
    1   41    1   48   39   25    1  112   14   45
   20   56    1   81   16   92   22   31    1   92
    1   33   51  192   18   61    1   72   26   59
    1  156    1   39   55   80   18   71    1  176
  108   43    1  124   22   45   32  140    1  123
   20   96   34   49   24  272    1   77   75  140

FreeBASIC

Function aDerivative(Byval n As Longint) As Longint
    If n < 0 Then Return -aDerivative(-n)
    If n = 0 Or n = 1 Then Return 0
    If n = 2 Then Return 1
    
    Dim As Longint q, d = 2
    Dim As Longint result = 1
    
    While d * d <= n
        If n Mod d = 0 Then
            q = n \ d
            result = q * aDerivative(d) + d * aDerivative(q)
            Exit While
        End If
        d += 1
    Wend
    
    Return result
End Function

'Main program
Print "Arithmetic derivatives for -99 through 100:"

Dim As Integer col, n
col = 0
For n = -99 To 100
    col += 1
    Print Using "####"; aDerivative(n);
    If col = 10 Then
        Print
        col = 0
    Else
        Print " ";
    End If
Next

'Stretch task
Print !"\n\nPowers of 10 derivatives divided by 7:"
Dim As Double m = 1
For n = 1 To 18 ' LongInt limit in FreeBASIC
    m *= 10
    Dim As Longint a = aDerivative(Clngint(m))
    Print Using "D(10^&) / 7 = &"; n; a \ 7
Next

Sleep
Output:
Arithmetic derivatives for -99 through 100:
 -75  -77   -1 -272  -24  -49  -34  -96  -20 -123
  -1 -140  -32  -45  -22 -124   -1  -43 -108 -176
  -1  -71  -18  -80  -55  -39   -1 -156   -1  -59
 -26  -72   -1  -61  -18 -192  -51  -33   -1  -92
  -1  -31  -22  -92  -16  -81   -1  -56  -20  -45
 -14 -112   -1  -25  -39  -48   -1  -41   -1  -68
 -16  -21   -1  -60  -12  -19  -14  -80   -1  -31
  -1  -32  -27  -15  -10  -44   -1  -13  -10  -24
  -1  -21   -1  -32   -8   -9   -1  -16   -1   -7
  -6  -12   -1   -5   -1   -4   -1   -1    0    0
   0    1    1    4    1    5    1   12    6    7
   1   16    1    9    8   32    1   21    1   24
  10   13    1   44   10   15   27   32    1   31
   1   80   14   19   12   60    1   21   16   68
   1   41    1   48   39   25    1  112   14   45
  20   56    1   81   16   92   22   31    1   92
   1   33   51  192   18   61    1   72   26   59
   1  156    1   39   55   80   18   71    1  176
 108   43    1  124   22   45   32  140    1  123
  20   96   34   49   24  272    1   77   75  140

Powers of 10 derivatives divided by 7:
D(10^1)/7 = 1
D(10^2)/7 = 20
D(10^3)/7 = 300
D(10^4)/7 = 4000
D(10^5)/7 = 50000
D(10^6)/7 = 600000
D(10^7)/7 = 7000000
D(10^8)/7 = 80000000
D(10^9)/7 = 900000000
D(10^10)/7 = 10000000000
D(10^11)/7 = 110000000000
D(10^12)/7 = 1200000000000
D(10^13)/7 = 13000000000000
D(10^14)/7 = 140000000000000
D(10^15)/7 = 1500000000000000
D(10^16)/7 = 16000000000000000
D(10^17)/7 = 170000000000000000

FutureBasic

Translation of: BASIC
// Arithmetic Derivative
//  https://rosettacode.org/wiki/Arithmetic_derivative#

local fn DoIt( N as short) as short
  short L,F,Z
  L = 0: F = 3: Z = ABS(N)
  IF Z<2 THEN exit fn
  
  1 IF Z MOD 2 = 0 THEN L=L+N\2: Z=Z\2: GOTO 1
  2  IF F>Z THEN exit fn
  3 IF Z MOD F = 0 THEN L=L+N\F: Z=Z\F: GOTO 2
  
  F=F+2
  goto 1
  
end fn = L

_Window = 1

window _Window,@"Arithmetic Derivative",fn cgrectmake(0,0,640,400)
windowcenter(_Window)

short N,L,LineCount
FOR N = -99 TO 100
L = fn DoIt(N): PRINT USING "########";L;
LineCount ++
if LineCount = 10 then print : LineCount = 0
NEXT

handleevents
Output:
 -75  -77   -1 -272  -24  -49  -34  -96  -20 -123
  -1 -140  -32  -45  -22 -124   -1  -43 -108 -176
  -1  -71  -18  -80  -55  -39   -1 -156   -1  -59
 -26  -72   -1  -61  -18 -192  -51  -33   -1  -92
  -1  -31  -22  -92  -16  -81   -1  -56  -20  -45
 -14 -112   -1  -25  -39  -48   -1  -41   -1  -68
 -16  -21   -1  -60  -12  -19  -14  -80   -1  -31
  -1  -32  -27  -15  -10  -44   -1  -13  -10  -24
  -1  -21   -1  -32   -8   -9   -1  -16   -1   -7
  -6  -12   -1   -5   -1   -4   -1   -1    0    0
   0    1    1    4    1    5    1   12    6    7
   1   16    1    9    8   32    1   21    1   24
  10   13    1   44   10   15   27   32    1   31
   1   80   14   19   12   60    1   21   16   68
   1   41    1   48   39   25    1  112   14   45
  20   56    1   81   16   92   22   31    1   92
   1   33   51  192   18   61    1   72   26   59
   1  156    1   39   55   80   18   71    1  176
 108   43    1  124   22   45   32  140    1  123
  20   96   34   49   24  272    1   77   75  140

Go

Library: Go-rcu

Using float64 (finessed a little) to avoid the unpleasantness of math/big for the stretch goal. Assumes that int type is 64 bit.

package main

import (
    "fmt"
    "rcu"
)

func D(n float64) float64 {
    if n < 0 {
        return -D(-n)
    }
    if n < 2 {
        return 0
    }
    var f []int
    if n < 1e19 {
        f = rcu.PrimeFactors(int(n))
    } else {
        g := int(n / 100)
        f = rcu.PrimeFactors(g)
        f = append(f, []int{2, 2, 5, 5}...)
    }
    c := len(f)
    if c == 1 {
        return 1
    }
    if c == 2 {
        return float64(f[0] + f[1])
    }
    d := n / float64(f[0])
    return D(d)*float64(f[0]) + d
}

func main() {
    ad := make([]int, 200)
    for n := -99; n < 101; n++ {
        ad[n+99] = int(D(float64(n)))
    }
    rcu.PrintTable(ad, 10, 4, false)
    fmt.Println()
    pow := 1.0
    for m := 1; m < 21; m++ {
        pow *= 10
        fmt.Printf("D(10^%-2d) / 7 = %.0f\n", m, D(pow)/7)
    }
}
Output:
 -75  -77   -1 -272  -24  -49  -34  -96  -20 -123 
  -1 -140  -32  -45  -22 -124   -1  -43 -108 -176 
  -1  -71  -18  -80  -55  -39   -1 -156   -1  -59 
 -26  -72   -1  -61  -18 -192  -51  -33   -1  -92 
  -1  -31  -22  -92  -16  -81   -1  -56  -20  -45 
 -14 -112   -1  -25  -39  -48   -1  -41   -1  -68 
 -16  -21   -1  -60  -12  -19  -14  -80   -1  -31 
  -1  -32  -27  -15  -10  -44   -1  -13  -10  -24 
  -1  -21   -1  -32   -8   -9   -1  -16   -1   -7 
  -6  -12   -1   -5   -1   -4   -1   -1    0    0 
   0    1    1    4    1    5    1   12    6    7 
   1   16    1    9    8   32    1   21    1   24 
  10   13    1   44   10   15   27   32    1   31 
   1   80   14   19   12   60    1   21   16   68 
   1   41    1   48   39   25    1  112   14   45 
  20   56    1   81   16   92   22   31    1   92 
   1   33   51  192   18   61    1   72   26   59 
   1  156    1   39   55   80   18   71    1  176 
 108   43    1  124   22   45   32  140    1  123 
  20   96   34   49   24  272    1   77   75  140 

D(10^1 ) / 7 = 1
D(10^2 ) / 7 = 20
D(10^3 ) / 7 = 300
D(10^4 ) / 7 = 4000
D(10^5 ) / 7 = 50000
D(10^6 ) / 7 = 600000
D(10^7 ) / 7 = 7000000
D(10^8 ) / 7 = 80000000
D(10^9 ) / 7 = 900000000
D(10^10) / 7 = 10000000000
D(10^11) / 7 = 110000000000
D(10^12) / 7 = 1200000000000
D(10^13) / 7 = 13000000000000
D(10^14) / 7 = 140000000000000
D(10^15) / 7 = 1500000000000000
D(10^16) / 7 = 16000000000000000
D(10^17) / 7 = 170000000000000000
D(10^18) / 7 = 1800000000000000000
D(10^19) / 7 = 19000000000000000000
D(10^20) / 7 = 200000000000000000000

Haskell

import Control.Monad (forM_)
import Data.List (intercalate)
import Data.List.Split (chunksOf)
import Math.NumberTheory.Primes (factorise, unPrime)
import Text.Printf (printf)

-- The arithmetic derivative of a number, which is assumed to be non-negative.
arithderiv_ :: Integer -> Integer
arithderiv_ 0 = 0
arithderiv_ n = foldr step 0 $ factorise n
  where step (p, v) s = s + n `quot` unPrime p * fromIntegral v

-- The arithmetic derivative of any integer.
arithderiv :: Integer -> Integer
arithderiv n | n < 0     = negate $ arithderiv_ (negate n)
             | otherwise = arithderiv_ n

printTable :: [Integer] -> IO ()
printTable = putStrLn
           . intercalate "\n"
           . map unwords
           . chunksOf 10
           . map (printf "%5d")

main :: IO ()
main = do
  printTable [arithderiv n | n <- [-99..100]]
  putStrLn ""
  forM_ [1..20 :: Integer] $ \i ->
    let q = 7
        n = arithderiv (10^i) `quot` q
    in printf "D(10^%-2d) / %d = %d\n" i q n
Output:
$ arithderiv
  -75   -77    -1  -272   -24   -49   -34   -96   -20  -123
   -1  -140   -32   -45   -22  -124    -1   -43  -108  -176
   -1   -71   -18   -80   -55   -39    -1  -156    -1   -59
  -26   -72    -1   -61   -18  -192   -51   -33    -1   -92
   -1   -31   -22   -92   -16   -81    -1   -56   -20   -45
  -14  -112    -1   -25   -39   -48    -1   -41    -1   -68
  -16   -21    -1   -60   -12   -19   -14   -80    -1   -31
   -1   -32   -27   -15   -10   -44    -1   -13   -10   -24
   -1   -21    -1   -32    -8    -9    -1   -16    -1    -7
   -6   -12    -1    -5    -1    -4    -1    -1     0     0
    0     1     1     4     1     5     1    12     6     7
    1    16     1     9     8    32     1    21     1    24
   10    13     1    44    10    15    27    32     1    31
    1    80    14    19    12    60     1    21    16    68
    1    41     1    48    39    25     1   112    14    45
   20    56     1    81    16    92    22    31     1    92
    1    33    51   192    18    61     1    72    26    59
    1   156     1    39    55    80    18    71     1   176
  108    43     1   124    22    45    32   140     1   123
   20    96    34    49    24   272     1    77    75   140

D(10^1 ) / 7 = 1
D(10^2 ) / 7 = 20
D(10^3 ) / 7 = 300
D(10^4 ) / 7 = 4000
D(10^5 ) / 7 = 50000
D(10^6 ) / 7 = 600000
D(10^7 ) / 7 = 7000000
D(10^8 ) / 7 = 80000000
D(10^9 ) / 7 = 900000000
D(10^10) / 7 = 10000000000
D(10^11) / 7 = 110000000000
D(10^12) / 7 = 1200000000000
D(10^13) / 7 = 13000000000000
D(10^14) / 7 = 140000000000000
D(10^15) / 7 = 1500000000000000
D(10^16) / 7 = 16000000000000000
D(10^17) / 7 = 170000000000000000
D(10^18) / 7 = 1800000000000000000
D(10^19) / 7 = 19000000000000000000
D(10^20) / 7 = 200000000000000000000

J

Implementation:

D=: {{ +/y%q:1>.|y }}"0

In other words: find the sum of the argument divided by each of the sequence of prime factors of its absolute value (with a special case for zero -- we use the maximum of either 1 or that absolute value when finding the sequence of prime factors).

Task example:

   D _99+i.20 10
_75  _77  _1 _272 _24  _49 _34  _96  _20 _123
 _1 _140 _32  _45 _22 _124  _1  _43 _108 _176
 _1  _71 _18  _80 _55  _39  _1 _156   _1  _59
_26  _72  _1  _61 _18 _192 _51  _33   _1  _92
 _1  _31 _22  _92 _16  _81  _1  _56  _20  _45
_14 _112  _1  _25 _39  _48  _1  _41   _1  _68
_16  _21  _1  _60 _12  _19 _14  _80   _1  _31
 _1  _32 _27  _15 _10  _44  _1  _13  _10  _24
 _1  _21  _1  _32  _8   _9  _1  _16   _1   _7
 _6  _12  _1   _5  _1   _4  _1   _1    0    0
  0    1   1    4   1    5   1   12    6    7
  1   16   1    9   8   32   1   21    1   24
 10   13   1   44  10   15  27   32    1   31
  1   80  14   19  12   60   1   21   16   68
  1   41   1   48  39   25   1  112   14   45
 20   56   1   81  16   92  22   31    1   92
  1   33  51  192  18   61   1   72   26   59
  1  156   1   39  55   80  18   71    1  176
108   43   1  124  22   45  32  140    1  123
 20   96  34   49  24  272   1   77   75  140

Also, it seems like it's worth verifying that order of evaluation does not create an ambiguity for the value of D (order shouldn't matter, since summation of integers is order independent):

   15 10 6 + 2 3 5 * D 15 10 6
31 31 31

Stretch task:

   (D 10x^1+i.4 5)%7
                1                 20                 300                 4000                 50000
           600000            7000000            80000000            900000000           10000000000
     110000000000      1200000000000      13000000000000      140000000000000      1500000000000000
16000000000000000 170000000000000000 1800000000000000000 19000000000000000000 200000000000000000000

Java

import java.math.BigInteger;

public final class ArithmeticDerivative {

	public static void main(String[] aArgs) {
        System.out.println("Arithmetic derivatives for -99 to 100 inclusive:");        
		for ( int n = -99, column = 0; n <= 100; n++ ) {
			System.out.print(String.format("%4d%s",
				derivative(BigInteger.valueOf(n)), ( ++column % 10 == 0 ) ? "\n" : " "));
		}
		System.out.println();
		
		final BigInteger seven = BigInteger.valueOf(7);
		for ( int power = 1; power <= 20; power++ ) {
			System.out.println(String.format("%s%2d%s%d",
				"D(10^", power, ") / 7 = ", derivative(BigInteger.TEN.pow(power)).divide(seven)));
		}
	}
	
	private static BigInteger derivative(BigInteger aNumber) {
		if ( aNumber.signum() == -1 ) {
			return derivative(aNumber.negate()).negate();
		}
		if ( aNumber == BigInteger.ZERO || aNumber == BigInteger.ONE ) {
			return BigInteger.ZERO;
		}
		BigInteger divisor = BigInteger.TWO;
		while ( divisor.multiply(divisor).compareTo(aNumber) <= 0 ) {
		    if ( aNumber.mod(divisor).signum() == 0 ) {
		        final BigInteger quotient = aNumber.divide(divisor);
		        return quotient.multiply(derivative(divisor)).add(divisor.multiply(derivative(quotient)));
		    }
		    divisor = divisor.add(BigInteger.ONE);
		}
		return BigInteger.ONE;
	}

}
Output:
Arithmetic derivatives for -99 to 100 inclusive:
 -75  -77   -1 -272  -24  -49  -34  -96  -20 -123
  -1 -140  -32  -45  -22 -124   -1  -43 -108 -176
  -1  -71  -18  -80  -55  -39   -1 -156   -1  -59
 -26  -72   -1  -61  -18 -192  -51  -33   -1  -92
  -1  -31  -22  -92  -16  -81   -1  -56  -20  -45
 -14 -112   -1  -25  -39  -48   -1  -41   -1  -68
 -16  -21   -1  -60  -12  -19  -14  -80   -1  -31
  -1  -32  -27  -15  -10  -44   -1  -13  -10  -24
  -1  -21   -1  -32   -8   -9   -1  -16   -1   -7
  -6  -12   -1   -5   -1   -4   -1   -1   -1    0
   0    1    1    4    1    5    1   12    6    7
   1   16    1    9    8   32    1   21    1   24
  10   13    1   44   10   15   27   32    1   31
   1   80   14   19   12   60    1   21   16   68
   1   41    1   48   39   25    1  112   14   45
  20   56    1   81   16   92   22   31    1   92
   1   33   51  192   18   61    1   72   26   59
   1  156    1   39   55   80   18   71    1  176
 108   43    1  124   22   45   32  140    1  123
  20   96   34   49   24  272    1   77   75  140

D(10^ 1) / 7 = 1
D(10^ 2) / 7 = 20
D(10^ 3) / 7 = 300
D(10^ 4) / 7 = 4000
D(10^ 5) / 7 = 50000
D(10^ 6) / 7 = 600000
D(10^ 7) / 7 = 7000000
D(10^ 8) / 7 = 80000000
D(10^ 9) / 7 = 900000000
D(10^10) / 7 = 10000000000
D(10^11) / 7 = 110000000000
D(10^12) / 7 = 1200000000000
D(10^13) / 7 = 13000000000000
D(10^14) / 7 = 140000000000000
D(10^15) / 7 = 1500000000000000
D(10^16) / 7 = 16000000000000000
D(10^17) / 7 = 170000000000000000
D(10^18) / 7 = 1800000000000000000
D(10^19) / 7 = 19000000000000000000
D(10^20) / 7 = 200000000000000000000

jq

For this task, gojq (the Go implementation of jq) is used for numerical accuracy, though the C implementation has sufficient accuracy at least for D(10^16).

See Prime_decomposition#jq for the def of factors/0 used here.

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

# In case gojq is used:
def _nwise($n):
  def nw: if length <= $n then . else .[0:$n] , (.[$n:] | nw) end;
  nw;

def lpad($len): tostring | ($len - length) as $l | (" " * $l)[:$l] + .;

def D($n):
    if   $n < 0 then -D(- $n)
    elif $n < 2 then 0
    else [$n | factors] as $f
    | ($f|length) as $c
    | if   $c <= 1 then 1
      elif $c == 2 then $f[0] + $f[1]
      else ($n / $f[0]) as $d
      | D($d) * $f[0] + $d
      end
    end ;

def task:
  def task1:
    reduce range(-99; 101) as $n ([]; .[$n+99] = D($n))
    | _nwise(10) | map(lpad(4)) | join(" ");

  def task2:
    range(1; 21) as $i
    | "D(10^\($i)) / 7 = \( D(10|power($i))/7 )" ;

  task1, "", task2 ;

task
Output:
 -75  -77   -1 -272  -24  -49  -34  -96  -20 -123
  -1 -140  -32  -45  -22 -124   -1  -43 -108 -176
  -1  -71  -18  -80  -55  -39   -1 -156   -1  -59
 -26  -72   -1  -61  -18 -192  -51  -33   -1  -92
  -1  -31  -22  -92  -16  -81   -1  -56  -20  -45
 -14 -112   -1  -25  -39  -48   -1  -41   -1  -68
 -16  -21   -1  -60  -12  -19  -14  -80   -1  -31
  -1  -32  -27  -15  -10  -44   -1  -13  -10  -24
  -1  -21   -1  -32   -8   -9   -1  -16   -1   -7
  -6  -12   -1   -5   -1   -4   -1   -1    0    0
   0    1    1    4    1    5    1   12    6    7
   1   16    1    9    8   32    1   21    1   24
  10   13    1   44   10   15   27   32    1   31
   1   80   14   19   12   60    1   21   16   68
   1   41    1   48   39   25    1  112   14   45
  20   56    1   81   16   92   22   31    1   92
   1   33   51  192   18   61    1   72   26   59
   1  156    1   39   55   80   18   71    1  176
 108   43    1  124   22   45   32  140    1  123
  20   96   34   49   24  272    1   77   75  140

D(10^1) / 7 = 1
D(10^2) / 7 = 20
D(10^3) / 7 = 300
D(10^4) / 7 = 4000
D(10^5) / 7 = 50000
D(10^6) / 7 = 600000
D(10^7) / 7 = 7000000
D(10^8) / 7 = 80000000
D(10^9) / 7 = 900000000
D(10^10) / 7 = 10000000000
D(10^11) / 7 = 110000000000
D(10^12) / 7 = 1200000000000
D(10^13) / 7 = 13000000000000
D(10^14) / 7 = 140000000000000
D(10^15) / 7 = 1500000000000000
D(10^16) / 7 = 16000000000000000
D(10^17) / 7 = 170000000000000000
D(10^18) / 7 = 1800000000000000000
D(10^19) / 7 = 19000000000000000000
D(10^20) / 7 = 200000000000000000000

Julia

using Primes

D(n) = n < 0 ? -D(-n) : n < 2 ? zero(n) : isprime(n) ? one(n) : typeof(n)(sum(e * n ÷ p for (p, e) in eachfactor(n)))

foreach(p -> print(lpad(p[2], 5), p[1] % 10 == 0 ? "\n" : ""), pairs(map(D, -99:100)))

println()
for m in 1:20
    println("D for 10^", rpad(m, 3), "divided by 7 is ", D(Int128(10)^m) ÷ 7)
end
Output:
  -75  -77   -1 -272  -24  -49  -34  -96  -20 -123
   -1 -140  -32  -45  -22 -124   -1  -43 -108 -176
   -1  -71  -18  -80  -55  -39   -1 -156   -1  -59
  -26  -72   -1  -61  -18 -192  -51  -33   -1  -92
   -1  -31  -22  -92  -16  -81   -1  -56  -20  -45
  -14 -112   -1  -25  -39  -48   -1  -41   -1  -68
  -16  -21   -1  -60  -12  -19  -14  -80   -1  -31
   -1  -32  -27  -15  -10  -44   -1  -13  -10  -24
   -1  -21   -1  -32   -8   -9   -1  -16   -1   -7
   -6  -12   -1   -5   -1   -4   -1   -1    0    0
    0    1    1    4    1    5    1   12    6    7
    1   16    1    9    8   32    1   21    1   24
   10   13    1   44   10   15   27   32    1   31
    1   80   14   19   12   60    1   21   16   68
    1   41    1   48   39   25    1  112   14   45
   20   56    1   81   16   92   22   31    1   92
    1   33   51  192   18   61    1   72   26   59
    1  156    1   39   55   80   18   71    1  176
  108   43    1  124   22   45   32  140    1  123
   20   96   34   49   24  272    1   77   75  140

D for 10^1  divided by 7 is 1
D for 10^2  divided by 7 is 20
D for 10^3  divided by 7 is 300
D for 10^4  divided by 7 is 4000
D for 10^5  divided by 7 is 50000
D for 10^6  divided by 7 is 600000
D for 10^7  divided by 7 is 7000000
D for 10^8  divided by 7 is 80000000
D for 10^9  divided by 7 is 900000000
D for 10^10 divided by 7 is 10000000000
D for 10^11 divided by 7 is 110000000000
D for 10^12 divided by 7 is 1200000000000
D for 10^13 divided by 7 is 13000000000000
D for 10^14 divided by 7 is 140000000000000
D for 10^15 divided by 7 is 1500000000000000
D for 10^16 divided by 7 is 16000000000000000
D for 10^17 divided by 7 is 170000000000000000
D for 10^18 divided by 7 is 1800000000000000000
D for 10^19 divided by 7 is 19000000000000000000
D for 10^20 divided by 7 is 200000000000000000000

Lua

Translation of: ALGOL 68 – with condensed output and only showing D values up to 10^17 as 10^18 onwards overflows

Tested with Lua 5.1 (LuaJIT and OpenResty), 5.3.6 and 5.4.6.
Lua 5.2.4 didn't like the string.format. Also the format of the larger D values appears to be sensitive to the Lua version.

do    local function lagarias (n) -- Lagarias arithmetic derivative
           if n < 0
           then return -lagarias (-n)
           elseif n == 0 or n == 1
           then return 0
           else local function smallPf (j, k) -- Smallest prime factor
                    if j % k == 0 then return k else return smallPf (j, k + 1) end
                end
                local f = smallPf (n, 2) local q = math.floor (n / f) 
                if q == 1
                then return 1
                else return q * lagarias (f) + f * lagarias (q)
                end
           end
      end
      for n = -99,100
      do io.write (string.format("%6d", lagarias (n)))
         if n % 10 == 0 then io.write ("\n") end
      end
      io.write ("\n")
      for n = 1,17     -- 18, 19 and 20 would overflow
      do local m = 10 ^ n
         io.write ("D(", string.format ("%d", m), ") / 7 = ", math.floor (lagarias (m) / 7), "\n")
      end
end
Output:
   -75   -77    -1  -272   -24   -49   -34   -96   -20  -123
    -1  -140   -32   -45   -22  -124    -1   -43  -108  -176
    -1   -71   -18   -80   -55   -39    -1  -156    -1   -59
   -26   -72    -1   -61   -18  -192   -51   -33    -1   -92
    -1   -31   -22   -92   -16   -81    -1   -56   -20   -45
   -14  -112    -1   -25   -39   -48    -1   -41    -1   -68
   -16   -21    -1   -60   -12   -19   -14   -80    -1   -31
    -1   -32   -27   -15   -10   -44    -1   -13   -10   -24
    -1   -21    -1   -32    -8    -9    -1   -16    -1    -7
    -6   -12    -1    -5    -1    -4    -1    -1     0     0
     0     1     1     4     1     5     1    12     6     7
     1    16     1     9     8    32     1    21     1    24
    10    13     1    44    10    15    27    32     1    31
     1    80    14    19    12    60     1    21    16    68
     1    41     1    48    39    25     1   112    14    45
    20    56     1    81    16    92    22    31     1    92
     1    33    51   192    18    61     1    72    26    59
     1   156     1    39    55    80    18    71     1   176
   108    43     1   124    22    45    32   140     1   123
    20    96    34    49    24   272     1    77    75   140

D(10) / 7 = 1
D(100) / 7 = 20
D(1000) / 7 = 300
D(10000) / 7 = 4000
D(100000) / 7 = 50000
D(1000000) / 7 = 600000
D(10000000) / 7 = 7000000
D(100000000) / 7 = 80000000
D(1000000000) / 7 = 900000000
D(10000000000) / 7 = 10000000000
D(100000000000) / 7 = 110000000000
D(1000000000000) / 7 = 1200000000000
D(10000000000000) / 7 = 13000000000000
D(100000000000000) / 7 = 140000000000000
D(1000000000000000) / 7 = 1500000000000000
D(10000000000000000) / 7 = 16000000000000000
D(100000000000000000) / 7 = 170000000000000000

MAD

            NORMAL MODE IS INTEGER

            INTERNAL FUNCTION(X,Y)
            ENTRY TO REM.
            FUNCTION RETURN X-(X/Y)*Y
            END OF FUNCTION

            INTERNAL FUNCTION(N)
            ENTRY TO DERIV.
            R = N
            WHENEVER R.L.0, R = -R
            WHENEVER R.L.2, FUNCTION RETURN 0
            S = 0
FAC2        WHENEVER REM.(R,2).E.0
                S = S + N/2
                R = R/2
                TRANSFER TO FAC2
            END OF CONDITIONAL
            THROUGH FAC, FOR F=3, 2, F.G.R
FACF        WHENEVER REM.(R,F).E.0
                S = S + N/F
                R = R/F
                TRANSFER TO FACF
            END OF CONDITIONAL
FAC         CONTINUE
            FUNCTION RETURN S
            END OF FUNCTION

            VECTOR VALUES LINEF = $10(I6)*$
            DIMENSION LINE(10)
            C = 0
            THROUGH ITEM, FOR I=-99, 1, I.G.100
            LINE(C) = DERIV.(I)
            C = C+1
            WHENEVER C.E.10
                PRINT FORMAT LINEF,
          0           LINE(0),LINE(1),LINE(2),LINE(3),LINE(4),
          1           LINE(5),LINE(6),LINE(7),LINE(8),LINE(9)
                C = 0
            END OF CONDITIONAL
ITEM        CONTINUE
            END OF PROGRAM
Output:
   -75   -77    -1  -272   -24   -49   -34   -96   -20  -123
    -1  -140   -32   -45   -22  -124    -1   -43  -108  -176
    -1   -71   -18   -80   -55   -39    -1  -156    -1   -59
   -26   -72    -1   -61   -18  -192   -51   -33    -1   -92
    -1   -31   -22   -92   -16   -81    -1   -56   -20   -45
   -14  -112    -1   -25   -39   -48    -1   -41    -1   -68
   -16   -21    -1   -60   -12   -19   -14   -80    -1   -31
    -1   -32   -27   -15   -10   -44    -1   -13   -10   -24
    -1   -21    -1   -32    -8    -9    -1   -16    -1    -7
    -6   -12    -1    -5    -1    -4    -1    -1     0     0
     0     1     1     4     1     5     1    12     6     7
     1    16     1     9     8    32     1    21     1    24
    10    13     1    44    10    15    27    32     1    31
     1    80    14    19    12    60     1    21    16    68
     1    41     1    48    39    25     1   112    14    45
    20    56     1    81    16    92    22    31     1    92
     1    33    51   192    18    61     1    72    26    59
     1   156     1    39    55    80    18    71     1   176
   108    43     1   124    22    45    32   140     1   123
    20    96    34    49    24   272     1    77    75   140

Mathematica / Wolfram Language

(* Arithmetic derivative *)

ClearAll[d, twoFactorsOf];

twoFactorsOf[n_Integer?Positive] := Module[{factors = FactorInteger[n, 2], p, factor},
   If[Length[factors] == 1,
       factor = Flatten@factors;
        p = First@factor;
        factors = {factor - {0, 1}, {p, 1}};
   ];
   Return[Power@@@factors];
];

twoFactorsOf[n_Integer?Negative] := twoFactorsOf[-n] * {-1, -1};

d[0] = d[1] = 0;
d[p_Integer?PrimeQ] := 1;
d[n_Integer?Negative] := -d[-n];
d[mn_Integer] := Module[{m, n},
   {m, n} = twoFactorsOf[m n];
   Return[d[m] n + m d[n]];
];

SetAttributes[d, Listable];

(* Output *)

Partition[StringPadLeft[ToString /@ d[Range[-99, 100]], 5], UpTo[10]] // TableForm

StringJoin["d[10^", ToString@First[#], "]", If[First[#] <= 9, "  ", " "], "/ 7", 
    " = ", 
    ToString@Last[#]] & /@ Table[{n, d[10^n]/7}, {n, 1, 20}] // TableForm
Output:
   57	  -21	    1	  -80	  -24	  -49	  -34	   88	  -20	  -33
    1	  -52	  -32	  -45	  -22	  -68	    1	  -43	  -54	   64
    1	   59	  -18	   72	    5	  -39	    1	   12	    1	   39
  -26	   64	    1	   49	  -18	  -64	   33	  -33	    1	  -52
    1	  -31	  -22	  -36	  -16	  -45	    1	   48	  -20	   -5
  -14	   32	    1	  -25	   21	   40	    1	   29	    1	  -28
  -16	  -21	    1	   60	  -12	  -19	  -14	   16	    1	   19
    1	   24	    9	  -15	  -10	  -20	    1	  -13	  -10	   16
    1	    3	    1	  -16	   -8	   -9	    1	    8	    1	   -7
   -6	    4	    1	   -5	    1	   -4	    1	    1	    0	    0
    0	    1	    1	    4	    1	    5	    1	   12	    6	    7
    1	   16	    1	    9	    8	   32	    1	   21	    1	   24
   10	   13	    1	   44	   10	   15	   27	   32	    1	   31
    1	   80	   14	   19	   12	   60	    1	   21	   16	   68
    1	   41	    1	   48	   39	   25	    1	  112	   14	   45
   20	   56	    1	   81	   16	   92	   22	   31	    1	   92
    1	   33	   51	  192	   18	   61	    1	   72	   26	   59
    1	  156	    1	   39	   55	   80	   18	   71	    1	  176
  108	   43	    1	  124	   22	   45	   32	  140	    1	  123
   20	   96	   34	   49	   24	  272	    1	   77	   75	  140

d[10^1]  = 1
d[10^2]  = 20
d[10^3]  = 300
d[10^4]  = 4000
d[10^5]  = 50000
d[10^6]  = 600000
d[10^7]  = 7000000
d[10^8]  = 80000000
d[10^9]  = 900000000
d[10^10] = 10000000000
d[10^11] = 110000000000
d[10^12] = 1200000000000
d[10^13] = 13000000000000
d[10^14] = 140000000000000
d[10^15] = 1500000000000000
d[10^16] = 16000000000000000
d[10^17] = 170000000000000000
d[10^18] = 1800000000000000000
d[10^19] = 19000000000000000000
d[10^20] = 200000000000000000000

MiniScript

Translation of: ALGOL 68 – via Lua
lagarias = function (n) // Lagarias arithmetic derivative
   if n < 0 then
       return -lagarias (-n)
   else if n == 0 or n == 1 then
       return 0
   else
       smallPf = function (j, k) // Smallest prime factor
           if j % k == 0 then
               return k
           else
               return smallPf (j, k + 1)
           end if
       end function
       f = smallPf (n, 2)
       q = floor (n / f) 
       if q == 1 then
           return 1
       else
           return q * lagarias (f) + f * lagarias (q)
       end if
   end if
end function
fmt6 = function (n) // return a 6 character string representation of n
    s = str( n )
    if s.len > 5 then
        return s
    else
        return ( " " * ( 6 - s.len ) ) + s
    end if
end function
ad = ""
for n in range( -99, 100 )
    ad = ad + " " + fmt6( lagarias (n) )
    if n % 10 == 0 then
        print( ad )
        ad = ""
    end if
end for
print()
for n in range( 1, 17 )
    m = 10 ^ n
    print( "D(" + str(m) + ") / 7 = " + str( floor (lagarias (m) / 7) ) )
end for
Output:
    -75    -77     -1   -272    -24    -49    -34    -96    -20   -123
     -1   -140    -32    -45    -22   -124     -1    -43   -108   -176
     -1    -71    -18    -80    -55    -39     -1   -156     -1    -59
    -26    -72     -1    -61    -18   -192    -51    -33     -1    -92
     -1    -31    -22    -92    -16    -81     -1    -56    -20    -45
    -14   -112     -1    -25    -39    -48     -1    -41     -1    -68
    -16    -21     -1    -60    -12    -19    -14    -80     -1    -31
     -1    -32    -27    -15    -10    -44     -1    -13    -10    -24
     -1    -21     -1    -32     -8     -9     -1    -16     -1     -7
     -6    -12     -1     -5     -1     -4     -1     -1      0      0
      0      1      1      4      1      5      1     12      6      7
      1     16      1      9      8     32      1     21      1     24
     10     13      1     44     10     15     27     32      1     31
      1     80     14     19     12     60      1     21     16     68
      1     41      1     48     39     25      1    112     14     45
     20     56      1     81     16     92     22     31      1     92
      1     33     51    192     18     61      1     72     26     59
      1    156      1     39     55     80     18     71      1    176
    108     43      1    124     22     45     32    140      1    123
     20     96     34     49     24    272      1     77     75    140
 
D(10) / 7 = 1
D(100) / 7 = 20
D(1000) / 7 = 300
D(10000) / 7 = 4000
D(100000) / 7 = 50000
D(1000000) / 7 = 600000
D(10000000) / 7 = 7000000
D(100000000) / 7 = 80000000
D(1000000000) / 7 = 900000000
D(10000000000) / 7 = 10000000000
D(100000000000) / 7 = 110000000000
D(1000000000000) / 7 = 1200000000000
D(10000000000000) / 7 = 13000000000000
D(100000000000000) / 7 = 140000000000000
D(1000000000000000) / 7 = 1500000000000000
D(10000000000000000) / 7 = 16000000000000000
D(100000000000000000) / 7 = 170000000000000000
D(1000000000000000000) / 7 = 1800000000000000000
D(10000000000000000000) / 7 = 19000000000000000000
D(100000000000000000000) / 7 = 200000000000000000000

Miranda

main :: [sys_message]
main = [Stdout (table 10 7 (map (show . lagarias) [-99..100])),
        Stdout (lay (map ten_pow_m_div_7 [1..20]))]

ten_pow_m_div_7 :: num->[char]
ten_pow_m_div_7 m = "D(10^" ++ rjustify 2 (show m) ++ ") / 7 = " ++
                    show (lagarias (10^m) div 7)

table :: num->num->[[char]]->[char]
table w cw ls = lay [concat (map (rjustify cw) l) | l <- group w ls]

group :: num->[*]->[[*]]
group n [] = []
group n ls = take n ls : group n (drop n ls)

lagarias :: num->num
lagarias n = -lagarias (-n), if n<0
           = sum [n div f | f <- factors n], otherwise

factors :: num->[num]
factors n = f n 2
            where f n d = [], if d > n
                        = d : f (n div d) d, if n mod d = 0
                        = f n (d+1), otherwise
Output:
    -75    -77     -1   -272    -24    -49    -34    -96    -20   -123
     -1   -140    -32    -45    -22   -124     -1    -43   -108   -176
     -1    -71    -18    -80    -55    -39     -1   -156     -1    -59
    -26    -72     -1    -61    -18   -192    -51    -33     -1    -92
     -1    -31    -22    -92    -16    -81     -1    -56    -20    -45
    -14   -112     -1    -25    -39    -48     -1    -41     -1    -68
    -16    -21     -1    -60    -12    -19    -14    -80     -1    -31
     -1    -32    -27    -15    -10    -44     -1    -13    -10    -24
     -1    -21     -1    -32     -8     -9     -1    -16     -1     -7
     -6    -12     -1     -5     -1     -4     -1     -1      0      0
      0      1      1      4      1      5      1     12      6      7
      1     16      1      9      8     32      1     21      1     24
     10     13      1     44     10     15     27     32      1     31
      1     80     14     19     12     60      1     21     16     68
      1     41      1     48     39     25      1    112     14     45
     20     56      1     81     16     92     22     31      1     92
      1     33     51    192     18     61      1     72     26     59
      1    156      1     39     55     80     18     71      1    176
    108     43      1    124     22     45     32    140      1    123
     20     96     34     49     24    272      1     77     75    140
D(10^ 1) / 7 = 1
D(10^ 2) / 7 = 20
D(10^ 3) / 7 = 300
D(10^ 4) / 7 = 4000
D(10^ 5) / 7 = 50000
D(10^ 6) / 7 = 600000
D(10^ 7) / 7 = 7000000
D(10^ 8) / 7 = 80000000
D(10^ 9) / 7 = 900000000
D(10^10) / 7 = 10000000000
D(10^11) / 7 = 110000000000
D(10^12) / 7 = 1200000000000
D(10^13) / 7 = 13000000000000
D(10^14) / 7 = 140000000000000
D(10^15) / 7 = 1500000000000000
D(10^16) / 7 = 16000000000000000
D(10^17) / 7 = 170000000000000000
D(10^18) / 7 = 1800000000000000000
D(10^19) / 7 = 19000000000000000000
D(10^20) / 7 = 200000000000000000000

Nim

Library: Nim-Integers
import std/[strformat, strutils]
import integers


func aDerivative(n: int | Integer): typeof(n) =
  ## Recursively compute the arithmetic derivative.
  ## The function works with normal integers or big integers.
  ## Using a cache to store the derivatives would improve the
  ## performance, but this is not needed for these tasks.
  if n < 0: return -aDerivative(-n)
  if n == 0 or n == 1: return 0
  if n == 2: return 1
  var d = 2
  result = 1
  while d * d <= n:
    if n mod d == 0:
      let q = n div d
      result = q * aDerivative(d) + d * aDerivative(q)
      break
    inc d


### Task ###

echo "Arithmetic derivatives for -99 through 100:"

# We can use an "int" variable here.
var col = 0
for n in -99..100:
  inc col
  stdout.write &"{aDerivative(n):>4}"
  stdout.write if col == 10: '\n' else: ' '
  if col == 10: col = 0


### Stretch task ###

echo()

# To avoid overflow, we have to use an "Integer" variable.
var n = Integer(1)
for m in 1..20:
  n *= 10
  let a = aDerivative(n)
  let left = &"D(10^{m}) / 7"
  echo &"{left:>12} = {a div 7}"
Output:
Arithmetic derivatives for -99 through 100:
 -75  -77   -1 -272  -24  -49  -34  -96  -20 -123
  -1 -140  -32  -45  -22 -124   -1  -43 -108 -176
  -1  -71  -18  -80  -55  -39   -1 -156   -1  -59
 -26  -72   -1  -61  -18 -192  -51  -33   -1  -92
  -1  -31  -22  -92  -16  -81   -1  -56  -20  -45
 -14 -112   -1  -25  -39  -48   -1  -41   -1  -68
 -16  -21   -1  -60  -12  -19  -14  -80   -1  -31
  -1  -32  -27  -15  -10  -44   -1  -13  -10  -24
  -1  -21   -1  -32   -8   -9   -1  -16   -1   -7
  -6  -12   -1   -5   -1   -4   -1   -1    0    0
   0    1    1    4    1    5    1   12    6    7
   1   16    1    9    8   32    1   21    1   24
  10   13    1   44   10   15   27   32    1   31
   1   80   14   19   12   60    1   21   16   68
   1   41    1   48   39   25    1  112   14   45
  20   56    1   81   16   92   22   31    1   92
   1   33   51  192   18   61    1   72   26   59
   1  156    1   39   55   80   18   71    1  176
 108   43    1  124   22   45   32  140    1  123
  20   96   34   49   24  272    1   77   75  140

 D(10^1) / 7 = 1
 D(10^2) / 7 = 20
 D(10^3) / 7 = 300
 D(10^4) / 7 = 4000
 D(10^5) / 7 = 50000
 D(10^6) / 7 = 600000
 D(10^7) / 7 = 7000000
 D(10^8) / 7 = 80000000
 D(10^9) / 7 = 900000000
D(10^10) / 7 = 10000000000
D(10^11) / 7 = 110000000000
D(10^12) / 7 = 1200000000000
D(10^13) / 7 = 13000000000000
D(10^14) / 7 = 140000000000000
D(10^15) / 7 = 1500000000000000
D(10^16) / 7 = 16000000000000000
D(10^17) / 7 = 170000000000000000
D(10^18) / 7 = 1800000000000000000
D(10^19) / 7 = 19000000000000000000
D(10^20) / 7 = 200000000000000000000

Perl

Translation of: J
Library: ntheory
use v5.36;
use bigint;
no warnings 'uninitialized';
use List::Util 'max';
use ntheory 'factor';

sub table ($c, @V) { my $t = $c * (my $w = 2 + length max @V); ( sprintf( ('%'.$w.'d')x@V, @V) ) =~ s/.{1,$t}\K/\n/gr }

sub D ($n) {
    my(%f, $s);
    $f{$_}++ for factor max 1, my $nabs = abs $n;
    map { $s += $nabs * $f{$_} / $_ } keys %f;
    $n > 0 ? $s : -$s;
}

say table 10, map { D $_ } -99 .. 100;
say join "\n", map { sprintf('D(10**%-2d) / 7 == ', $_) . D(10**$_) / 7 } 1 .. 20;
Output:
  -75  -77   -1 -272  -24  -49  -34  -96  -20 -123
   -1 -140  -32  -45  -22 -124   -1  -43 -108 -176
   -1  -71  -18  -80  -55  -39   -1 -156   -1  -59
  -26  -72   -1  -61  -18 -192  -51  -33   -1  -92
   -1  -31  -22  -92  -16  -81   -1  -56  -20  -45
  -14 -112   -1  -25  -39  -48   -1  -41   -1  -68
  -16  -21   -1  -60  -12  -19  -14  -80   -1  -31
   -1  -32  -27  -15  -10  -44   -1  -13  -10  -24
   -1  -21   -1  -32   -8   -9   -1  -16   -1   -7
   -6  -12   -1   -5   -1   -4   -1   -1    0    0
    0    1    1    4    1    5    1   12    6    7
    1   16    1    9    8   32    1   21    1   24
   10   13    1   44   10   15   27   32    1   31
    1   80   14   19   12   60    1   21   16   68
    1   41    1   48   39   25    1  112   14   45
   20   56    1   81   16   92   22   31    1   92
    1   33   51  192   18   61    1   72   26   59
    1  156    1   39   55   80   18   71    1  176
  108   43    1  124   22   45   32  140    1  123
   20   96   34   49   24  272    1   77   75  140

D(10**1 ) / 7 == 1
D(10**2 ) / 7 == 20
D(10**3 ) / 7 == 300
D(10**4 ) / 7 == 4000
D(10**5 ) / 7 == 50000
D(10**6 ) / 7 == 600000
D(10**7 ) / 7 == 7000000
D(10**8 ) / 7 == 80000000
D(10**9 ) / 7 == 900000000
D(10**10) / 7 == 10000000000
D(10**11) / 7 == 110000000000
D(10**12) / 7 == 1200000000000
D(10**13) / 7 == 13000000000000
D(10**14) / 7 == 140000000000000
D(10**15) / 7 == 1500000000000000
D(10**16) / 7 == 16000000000000000
D(10**17) / 7 == 170000000000000000
D(10**18) / 7 == 1800000000000000000
D(10**19) / 7 == 19000000000000000000
D(10**20) / 7 == 200000000000000000000

PL/I

arithmeticDerivative: procedure options(main);
    lagarias: procedure(n) returns(fixed);
        declare (n, res, fac, rem) fixed;
        rem = abs(n);
        if rem<2 then return(0);

        res = 0;
        do while(mod(rem,2) = 0);
            res = res + n/2;
            rem = rem/2;
        end;

        do fac=3 repeat(fac+2) while(fac<=rem);
            do while(mod(rem,fac) = 0);
                res = res + n/fac;
                rem = rem/fac;
            end;
        end;
        return(res);
    end lagarias;

    declare n fixed;
    do n=-99 to 100;
        put edit(lagarias(n)) (F(7));
        if mod(n+100, 10)=0 then put skip;
    end;
end arithmeticDerivative;
Output:
    -75    -77     -1   -272    -24    -49    -34    -96    -20   -123
     -1   -140    -32    -45    -22   -124     -1    -43   -108   -176
     -1    -71    -18    -80    -55    -39     -1   -156     -1    -59
    -26    -72     -1    -61    -18   -192    -51    -33     -1    -92
     -1    -31    -22    -92    -16    -81     -1    -56    -20    -45
    -14   -112     -1    -25    -39    -48     -1    -41     -1    -68
    -16    -21     -1    -60    -12    -19    -14    -80     -1    -31
     -1    -32    -27    -15    -10    -44     -1    -13    -10    -24
     -1    -21     -1    -32     -8     -9     -1    -16     -1     -7
     -6    -12     -1     -5     -1     -4     -1     -1      0      0
      0      1      1      4      1      5      1     12      6      7
      1     16      1      9      8     32      1     21      1     24
     10     13      1     44     10     15     27     32      1     31
      1     80     14     19     12     60      1     21     16     68
      1     41      1     48     39     25      1    112     14     45
     20     56      1     81     16     92     22     31      1     92
      1     33     51    192     18     61      1     72     26     59
      1    156      1     39     55     80     18     71      1    176
    108     43      1    124     22     45     32    140      1    123
     20     96     34     49     24    272      1     77     75    140


PL/M

Works with: 8080 PL/M Compiler version under CP/M (or an emulator)
Translation of: BASIC – via Action!

The 8080 PL/M only has unsigned integer arithmetic with integers in the range 0-65535. By adding 32768 we can compare values in the range -32768-32767 and get the correct result. The arithmetic operations +, - and * will produce the correct results but division and MOD need special handling if the operands are signed. MOD is not needed for this sample but the SIGNED$LT and SIGNED$DIV procedures implement signed < and / operations.

100H: /* ARITHMETIC DERIVATIVE - BASED ON THE BASIC SAMPLE                   */

   /* RETURNS TRUE IF A < B, FALSE OTHERWISE WITH A AND B TREATED AS SIGNED  */
   SIGNED$LT: PROCEDURE( A, B )BYTE;
      DECLARE ( A, B ) ADDRESS;
      IF ( A + 32768 ) < ( B + 32768 ) THEN RETURN 0FFH; ELSE RETURN 0;
   END SIGNED$LT ;

   /* RETURNS A / B WITH A AND B TREATED AS SIGNED                           */
   SIGNED$DIV: PROCEDURE( AIN, BIN )ADDRESS;
      DECLARE ( AIN, BIN )ADDRESS;
      DECLARE ( A, B, SIGN )ADDRESS;
      SIGN = 1;
      A    = AIN;
      B    = BIN;
      IF SIGNED$LT( A, 0 ) THEN DO;
          SIGN = - SIGN;
          A    = - A;
      END;
      IF SIGNED$LT( B, 0 ) THEN DO;
          SIGN = - SIGN;
          B    = - B;
      END;
   RETURN ( A / B ) * SIGN;
   END SIGNED$DIV ;

   /* CP/M BDOS SYSTEM CALL AND I/O ROUTINES                                 */
   BDOS: PROCEDURE( FN, ARG ); DECLARE FN BYTE, ARG ADDRESS; GOTO 5; END;
   PR$CHAR:   PROCEDURE( C ); DECLARE C BYTE;    CALL BDOS( 2, C );  END;
   PR$STRING: PROCEDURE( S ); DECLARE S ADDRESS; CALL BDOS( 9, S );  END;
   PR$NL:     PROCEDURE;   CALL PR$CHAR( 0DH ); CALL PR$CHAR( 0AH ); END;

   PR$SIGNED$NUMBER: PROCEDURE( N ); /* PRINTS A SIGNED NUMBER               */
      DECLARE N ADDRESS;
      DECLARE V ADDRESS, N$STR ( 9 )BYTE, W BYTE;
      IF SIGNED$LT( N, 0 ) THEN V = - N; ELSE V = N;
      DO W = 0 TO LAST( N$STR ); N$STR( W ) = ' '; END;
      W = LAST( N$STR );
      N$STR( W ) = '$';
      N$STR( W := W - 1 ) = '0' + ( V MOD 10 );
      DO WHILE( ( V := V / 10 ) > 0 );
         N$STR( W := W - 1 ) = '0' + ( V MOD 10 );
      END;
      IF SIGNED$LT( N, 0 ) THEN N$STR( W := W - 1 ) = '-';
      CALL PR$STRING( .N$STR );
   END PR$SIGNED$NUMBER;

   /* TASK                                                                   */

   DECLARE ( C, N, L, F, Z ) ADDRESS;

   DO C = 1 TO 200;
      N = C - 100;
      L = 0; F = 3; IF SIGNED$LT( N, 0 ) THEN Z = - N; ELSE Z = N;
      DO WHILE Z >= 2;
         DO WHILE Z MOD 2 = 0;    L = L + SIGNED$DIV( N, 2 ); Z = Z / 2; END;
         IF F <= Z THEN DO;
            DO WHILE Z MOD F = 0; L = L + SIGNED$DIV( N, F ); Z = Z / F; END;
            F = F + 2;
         END;
      END;
      CALL PR$SIGNED$NUMBER( L ); 
      IF C MOD 10 = 0 THEN CALL PR$NL;
   END;

EOF
Output:
     -75     -77      -1    -272     -24     -49     -34     -96     -20    -123
      -1    -140     -32     -45     -22    -124      -1     -43    -108    -176
      -1     -71     -18     -80     -55     -39      -1    -156      -1     -59
     -26     -72      -1     -61     -18    -192     -51     -33      -1     -92
      -1     -31     -22     -92     -16     -81      -1     -56     -20     -45
     -14    -112      -1     -25     -39     -48      -1     -41      -1     -68
     -16     -21      -1     -60     -12     -19     -14     -80      -1     -31
      -1     -32     -27     -15     -10     -44      -1     -13     -10     -24
      -1     -21      -1     -32      -8      -9      -1     -16      -1      -7
      -6     -12      -1      -5      -1      -4      -1      -1       0       0
       0       1       1       4       1       5       1      12       6       7
       1      16       1       9       8      32       1      21       1      24
      10      13       1      44      10      15      27      32       1      31
       1      80      14      19      12      60       1      21      16      68
       1      41       1      48      39      25       1     112      14      45
      20      56       1      81      16      92      22      31       1      92
       1      33      51     192      18      61       1      72      26      59
       1     156       1      39      55      80      18      71       1     176
     108      43       1     124      22      45      32     140       1     123
      20      96      34      49      24     272       1      77      75     140

Phix

with javascript_semantics
include mpfr.e
procedure D(mpz n)
    integer s = mpz_cmp_si(n,0)
    if s<0 then mpz_neg(n,n) end if
    if mpz_cmp_si(n,2)<0 then
        mpz_set_si(n,0)
    else
        sequence f = mpz_prime_factors(n)
        integer c = sum(vslice(f,2)),
                f1 = f[1][1]
        if c=1 then
            mpz_set_si(n,1)
        elsif c=2 then
            mpz_set_si(n,f1 + iff(length(f)=1?f1:f[2][1]))
        else
            assert(mpz_fdiv_q_ui(n,n,f1)=0)
            mpz d = mpz_init_set(n)
            D(n)
            mpz_mul_si(n,n,f1)
            mpz_add(n,n,d)
        end if
        if s<0 then mpz_neg(n,n) end if
    end if
end procedure
 
sequence res = repeat(0,200)
mpz n = mpz_init()
for i=-99 to 100 do
    mpz_set_si(n,i)
    D(n)
    res[i+100] = mpz_get_str(n)
end for
printf(1,"%s\n\n",{join_by(res,1,10," ",fmt:="%4s")})
for m=1 to 20 do
    mpz_ui_pow_ui(n,10,m)
    D(n)
    assert(mpz_fdiv_q_ui(n,n,7)=0)
    printf(1,"D(10^%d)/7 = %s\n",{m,mpz_get_str(n)})
end for
Output:
 -75  -77   -1 -272  -24  -49  -34  -96  -20 -123
  -1 -140  -32  -45  -22 -124   -1  -43 -108 -176
  -1  -71  -18  -80  -55  -39   -1 -156   -1  -59
 -26  -72   -1  -61  -18 -192  -51  -33   -1  -92
  -1  -31  -22  -92  -16  -81   -1  -56  -20  -45
 -14 -112   -1  -25  -39  -48   -1  -41   -1  -68
 -16  -21   -1  -60  -12  -19  -14  -80   -1  -31
  -1  -32  -27  -15  -10  -44   -1  -13  -10  -24
  -1  -21   -1  -32   -8   -9   -1  -16   -1   -7
  -6  -12   -1   -5   -1   -4   -1   -1    0    0
   0    1    1    4    1    5    1   12    6    7
   1   16    1    9    8   32    1   21    1   24
  10   13    1   44   10   15   27   32    1   31
   1   80   14   19   12   60    1   21   16   68
   1   41    1   48   39   25    1  112   14   45
  20   56    1   81   16   92   22   31    1   92
   1   33   51  192   18   61    1   72   26   59
   1  156    1   39   55   80   18   71    1  176
 108   43    1  124   22   45   32  140    1  123
  20   96   34   49   24  272    1   77   75  140

D(10^1)/7 = 1
D(10^2)/7 = 20
D(10^3)/7 = 300
D(10^4)/7 = 4000
D(10^5)/7 = 50000
D(10^6)/7 = 600000
D(10^7)/7 = 7000000
D(10^8)/7 = 80000000
D(10^9)/7 = 900000000
D(10^10)/7 = 10000000000
D(10^11)/7 = 110000000000
D(10^12)/7 = 1200000000000
D(10^13)/7 = 13000000000000
D(10^14)/7 = 140000000000000
D(10^15)/7 = 1500000000000000
D(10^16)/7 = 16000000000000000
D(10^17)/7 = 170000000000000000
D(10^18)/7 = 1800000000000000000
D(10^19)/7 = 19000000000000000000
D(10^20)/7 = 200000000000000000000

Python

from sympy.ntheory import factorint

def D(n):
    if n < 0:
        return -D(-n)
    elif n < 2:
        return 0
    else:
        fdict = factorint(n)
        if len(fdict) == 1 and 1 in fdict: # is prime
            return 1
        return sum([n * e // p for p, e in fdict.items()])

for n in range(-99, 101):
    print('{:5}'.format(D(n)), end='\n' if n % 10 == 0 else '')

print()
for m in range(1, 21):
    print('(D for 10**{}) divided by 7 is {}'.format(m, D(10 ** m) // 7))
Output:
  -75  -77   -1 -272  -24  -49  -34  -96  -20 -123
   -1 -140  -32  -45  -22 -124   -1  -43 -108 -176
   -1  -71  -18  -80  -55  -39   -1 -156   -1  -59
  -26  -72   -1  -61  -18 -192  -51  -33   -1  -92
   -1  -31  -22  -92  -16  -81   -1  -56  -20  -45
  -14 -112   -1  -25  -39  -48   -1  -41   -1  -68
  -16  -21   -1  -60  -12  -19  -14  -80   -1  -31
   -1  -32  -27  -15  -10  -44   -1  -13  -10  -24
   -1  -21   -1  -32   -8   -9   -1  -16   -1   -7
   -6  -12   -1   -5   -1   -4   -1   -1    0    0
    0    1    1    4    1    5    1   12    6    7
    1   16    1    9    8   32    1   21    1   24
   10   13    1   44   10   15   27   32    1   31
    1   80   14   19   12   60    1   21   16   68
    1   41    1   48   39   25    1  112   14   45
   20   56    1   81   16   92   22   31    1   92
    1   33   51  192   18   61    1   72   26   59
    1  156    1   39   55   80   18   71    1  176
  108   43    1  124   22   45   32  140    1  123
   20   96   34   49   24  272    1   77   75  140

(D for 10**1) divided by 7 is 1
(D for 10**2) divided by 7 is 20
(D for 10**3) divided by 7 is 300
(D for 10**4) divided by 7 is 4000
(D for 10**5) divided by 7 is 50000
(D for 10**6) divided by 7 is 600000
(D for 10**7) divided by 7 is 7000000
(D for 10**8) divided by 7 is 80000000
(D for 10**9) divided by 7 is 900000000
(D for 10**10) divided by 7 is 10000000000
(D for 10**11) divided by 7 is 110000000000
(D for 10**12) divided by 7 is 1200000000000
(D for 10**13) divided by 7 is 13000000000000
(D for 10**14) divided by 7 is 140000000000000
(D for 10**15) divided by 7 is 1500000000000000
(D for 10**16) divided by 7 is 16000000000000000
(D for 10**17) divided by 7 is 170000000000000000
(D for 10**18) divided by 7 is 1800000000000000000
(D for 10**19) divided by 7 is 19000000000000000000
(D for 10**20) divided by 7 is 200000000000000000000

Quackery

primefactors is defined at Prime decomposition#Quackery.

  [ dup 0 < iff
      [ negate
        ' negate ]
    else []
    swap 0 over
    primefactors
    witheach
      [ dip over / + ]
    nip swap do ]      is d ( n --> n )

  200 times [ i^ 99 - d echo sp ]
  cr cr
  20 times [ 10 i^ 1+ ** d 7 / echo cr ]
Output:
-75 -77 -1 -272 -24 -49 -34 -96 -20 -123 -1 -140 -32 -45 -22 -124 -1 -43 -108 -176 -1 -71 -18 -80 -55 -39 -1 -156 -1 -59 -26 -72 -1 -61 -18 -192 -51 -33 -1 -92 -1 -31 -22 -92 -16 -81 -1 -56 -20 -45 -14 -112 -1 -25 -39 -48 -1 -41 -1 -68 -16 -21 -1 -60 -12 -19 -14 -80 -1 -31 -1 -32 -27 -15 -10 -44 -1 -13 -10 -24 -1 -21 -1 -32 -8 -9 -1 -16 -1 -7 -6 -12 -1 -5 -1 -4 -1 -1 0 0 0 1 1 4 1 5 1 12 6 7 1 16 1 9 8 32 1 21 1 24 10 13 1 44 10 15 27 32 1 31 1 80 14 19 12 60 1 21 16 68 1 41 1 48 39 25 1 112 14 45 20 56 1 81 16 92 22 31 1 92 1 33 51 192 18 61 1 72 26 59 1 156 1 39 55 80 18 71 1 176 108 43 1 124 22 45 32 140 1 123 20 96 34 49 24 272 1 77 75 140 

1
20
300
4000
50000
600000
7000000
80000000
900000000
10000000000
110000000000
1200000000000
13000000000000
140000000000000
1500000000000000
16000000000000000
170000000000000000
1800000000000000000
19000000000000000000
200000000000000000000

R

library(gmp) #for big number factorization

arithmetic_derivative<-function(x){
  if (x==0|x==1|x==-1){
    D=0
  }
  else{
    n=ifelse(x<0,-x,x)
    prime_decomposition <-as.numeric(factorize(n))
    if (length(prime_decomposition)==1){
      D<- 1
    }
    else{
      D<-sum(prime_decomposition[c(1,2)])
      if (length(prime_decomposition)>2){
        cumulative_prod <-cumprod(prime_decomposition)
        for (i in 3:length(prime_decomposition)){
          D<- D * prime_decomposition[i]  + cumulative_prod[i-1]
        }
      }
    }
    
  }
  sign(x)*D
}

print(t(matrix(sapply(-99:100,arithmetic_derivative),nrow=10)))

for (k in 1:20){
  x <- 10**k
  cat(paste0("D(",x,")/7 = ",arithmetic_derivative(x)/7,"\n"),sep = "")}

Output

     [,1] [,2] [,3] [,4] [,5] [,6] [,7] [,8] [,9] [,10]
 [1,]  -75  -77   -1 -272  -24  -49  -34  -96  -20  -123
 [2,]   -1 -140  -32  -45  -22 -124   -1  -43 -108  -176
 [3,]   -1  -71  -18  -80  -55  -39   -1 -156   -1   -59
 [4,]  -26  -72   -1  -61  -18 -192  -51  -33   -1   -92
 [5,]   -1  -31  -22  -92  -16  -81   -1  -56  -20   -45
 [6,]  -14 -112   -1  -25  -39  -48   -1  -41   -1   -68
 [7,]  -16  -21   -1  -60  -12  -19  -14  -80   -1   -31
 [8,]   -1  -32  -27  -15  -10  -44   -1  -13  -10   -24
 [9,]   -1  -21   -1  -32   -8   -9   -1  -16   -1    -7
[10,]   -6  -12   -1   -5   -1   -4   -1   -1    0     0
[11,]    0    1    1    4    1    5    1   12    6     7
[12,]    1   16    1    9    8   32    1   21    1    24
[13,]   10   13    1   44   10   15   27   32    1    31
[14,]    1   80   14   19   12   60    1   21   16    68
[15,]    1   41    1   48   39   25    1  112   14    45
[16,]   20   56    1   81   16   92   22   31    1    92
[17,]    1   33   51  192   18   61    1   72   26    59
[18,]    1  156    1   39   55   80   18   71    1   176
[19,]  108   43    1  124   22   45   32  140    1   123
[20,]   20   96   34   49   24  272    1   77   75   140
D(10)/7 = 1
D(100)/7 = 20
D(1000)/7 = 300
D(10000)/7 = 4000
D(1e+05)/7 = 50000
D(1e+06)/7 = 6e+05
D(1e+07)/7 = 7e+06
D(1e+08)/7 = 8e+07
D(1e+09)/7 = 9e+08
D(1e+10)/7 = 1e+10
D(1e+11)/7 = 1.1e+11
D(1e+12)/7 = 1.2e+12
D(1e+13)/7 = 1.3e+13
D(1e+14)/7 = 1.4e+14
D(1e+15)/7 = 1.5e+15
D(1e+16)/7 = 1.6e+16
D(1e+17)/7 = 1.7e+17
D(1e+18)/7 = 1.8e+18
D(1e+19)/7 = 1.9e+19
D(1e+20)/7 = 2e+20


Raku

use Prime::Factor;

multi D (0) { 0 }
multi D (1) { 0 }
multi D ($n where &is-prime) { 1 }
multi D ($n where * < 0 ) { -D -$n }
multi D ($n) { sum $n.&prime-factors.Bag.map: { $n × .value / .key } }


put (-99 .. 100).map(&D).batch(10)».fmt("%4d").join: "\n";

put '';

put join "\n", (1..20).map: { sprintf "D(10**%-2d) / 7 == %d", $_, D(10**$_) / 7 }
Output:
 -75  -77   -1 -272  -24  -49  -34  -96  -20 -123
  -1 -140  -32  -45  -22 -124   -1  -43 -108 -176
  -1  -71  -18  -80  -55  -39   -1 -156   -1  -59
 -26  -72   -1  -61  -18 -192  -51  -33   -1  -92
  -1  -31  -22  -92  -16  -81   -1  -56  -20  -45
 -14 -112   -1  -25  -39  -48   -1  -41   -1  -68
 -16  -21   -1  -60  -12  -19  -14  -80   -1  -31
  -1  -32  -27  -15  -10  -44   -1  -13  -10  -24
  -1  -21   -1  -32   -8   -9   -1  -16   -1   -7
  -6  -12   -1   -5   -1   -4   -1   -1    0    0
   0    1    1    4    1    5    1   12    6    7
   1   16    1    9    8   32    1   21    1   24
  10   13    1   44   10   15   27   32    1   31
   1   80   14   19   12   60    1   21   16   68
   1   41    1   48   39   25    1  112   14   45
  20   56    1   81   16   92   22   31    1   92
   1   33   51  192   18   61    1   72   26   59
   1  156    1   39   55   80   18   71    1  176
 108   43    1  124   22   45   32  140    1  123
  20   96   34   49   24  272    1   77   75  140

D(10**1 ) / 7 == 1
D(10**2 ) / 7 == 20
D(10**3 ) / 7 == 300
D(10**4 ) / 7 == 4000
D(10**5 ) / 7 == 50000
D(10**6 ) / 7 == 600000
D(10**7 ) / 7 == 7000000
D(10**8 ) / 7 == 80000000
D(10**9 ) / 7 == 900000000
D(10**10) / 7 == 10000000000
D(10**11) / 7 == 110000000000
D(10**12) / 7 == 1200000000000
D(10**13) / 7 == 13000000000000
D(10**14) / 7 == 140000000000000
D(10**15) / 7 == 1500000000000000
D(10**16) / 7 == 16000000000000000
D(10**17) / 7 == 170000000000000000
D(10**18) / 7 == 1800000000000000000
D(10**19) / 7 == 19000000000000000000
D(10**20) / 7 == 200000000000000000000

Refal

$ENTRY Go {
    = <Table 10 7 <Each (Lagarias) <Iota ('-'99) 100>>>
};

Lagarias {
    '-' e.N = '-' <Lagarias e.N>;
    0 = 0;
    1 = 0;
    e.N, <Fac e.N>: {
        e.N = 1;
        e.F, <Div (e.N) e.F>: e.R =
            <Add <Mul (e.R) <Lagarias e.F>>
                 <Mul (e.F) <Lagarias e.R>>>;
    }; 
};

Fac {
    (e.F) e.N, <Mul (e.N) e.N>: e.N2,
               <Compare (e.F) e.N2>: '+' = e.N;
    (e.F) e.N, <Mod (e.N) e.F>: 0 = e.F;
    (e.F) e.N = <Fac (<Add (1) e.F>) e.N>;
    e.N = <Fac (2) e.N>;
};

Table { s.C s.W e.L = <Each (Prout) <Each (Line s.W) <Group s.C e.L>>>; };
Line { s.W e.X = <Join <Each (Fmt s.W) e.X>>; };
Fmt { s.W e.X, <Last s.W <Rep s.W ' '> <Symb e.X>>: (e.Z) e.C = e.C; };
Rep { 0 s.C = ; s.N s.C = s.C <Rep <Sub s.N 1> s.C>; };
Join { = ; (e.X) e.Y = e.X <Join e.Y>; };
Group { s.N = ; s.N e.X, <First s.N e.X>: (e.G) e.R = (e.G) <Group s.N e.R>; };
Each { (e.F) = ; (e.F) (e.X) e.XS = (<Mu e.F e.X>) <Each (e.F) e.XS>; };
Iota { (e.E) e.E = (e.E); (e.S) e.E = (e.S) <Iota (<Add (1) e.S>) e.E>; };
Output:
    -75    -77     -1   -272    -24    -49    -34    -96    -20   -123
     -1   -140    -32    -45    -22   -124     -1    -43   -108   -176
     -1    -71    -18    -80    -55    -39     -1   -156     -1    -59
    -26    -72     -1    -61    -18   -192    -51    -33     -1    -92
     -1    -31    -22    -92    -16    -81     -1    -56    -20    -45
    -14   -112     -1    -25    -39    -48     -1    -41     -1    -68
    -16    -21     -1    -60    -12    -19    -14    -80     -1    -31
     -1    -32    -27    -15    -10    -44     -1    -13    -10    -24
     -1    -21     -1    -32     -8     -9     -1    -16     -1     -7
     -6    -12     -1     -5     -1     -4     -1     -1     -0      0
      0      1      1      4      1      5      1     12      6      7
      1     16      1      9      8     32      1     21      1     24
     10     13      1     44     10     15     27     32      1     31
      1     80     14     19     12     60      1     21     16     68
      1     41      1     48     39     25      1    112     14     45
     20     56      1     81     16     92     22     31      1     92
      1     33     51    192     18     61      1     72     26     59
      1    156      1     39     55     80     18     71      1    176
    108     43      1    124     22     45     32    140      1    123
     20     96     34     49     24    272      1     77     75    140

RPL

Works with: HP version 49
CASE
      DUP 0 < THEN NEG ADERIV NEG END
      DUP 2 < THEN DROP 0 END
      R→I DUP ISPRIME? THEN DROP 1 END
      DUP FACTORS HEAD LASTARG 2 GET DUP2 ^ 4 PICK OVER / 1 RND
      → n p k pk rem
      ≪ k pk p / * rem * rem ADERIV pk * +
      ≫
  END
≫ 'ADERIV' STO
≪ n ADERIV ≫ 'n' -99 100 1 SEQ
≪ 10 m ^ ADERIV 7 / R→I ≫ 'nm' 1 20 1 SEQ
Output:
2: {-75 -77 -1 -272 -24 -49 -34 -96 -20 -123 -1 -140 -32 -45 -22 -124 -1 -43 -108 -176 -1 -71 -18 -80 -55 -39 -1 -156 -1 -59 -26 -72 -1 -61 -18 -192 -51 -33 -1 -92 -1 -31 -22 -92 -16 -81 -1 -56 -20 -45 -14 -112 -1 -25 -39 -48 -1 -41 -1 -68 -16 -21 -1 -60 -12 -19 -14 -80 -1 -31 -1 -32 -27 -15 -10 -44 -1 -13 -10 -24 -1 -21 -1 -32 -8 -9 -1 -16 -1 -7 -6 -12 -1 -5 -1 -4 -1 -1 0 0 0 1 1 4 1 5 1 12 6 7 1 16 1 9 8 32 1 21 1 24 10 13 1 44 10 15 27 32 1 31 1 80 14 19 12 60 1 21 16 68 1 41 1 48 39 25 1 112 14 45 20 56 1 81 16 92 22 31 1 92 1 33 51 192 18 61 1 72 26 59 1 156 1 39 55 80 18 71 1 176 108 43 1 124 22 45 32 140 1 123 20 96 34 49 24 272 1 77 75 140}
1: {1 20 300 4000 50000 600000 7000000 80000000 900000000 10000000000 110000000000 1200000000000 13000000000000 140000000000000 1500000000000000 16000000000000000 170000000000000000 800000000000000000 19000000000000000000 200000000000000000000}

Rust

Translation of: Python
use prime_factorization::Factorization;

fn d(n: i128) -> i128 {
    if n < 0 {
        return -(d(-n));
    } else if n < 2 {
        return 0;
    } else {
        let fpairs = Factorization::run(n as u128).prime_factor_repr();
        if fpairs.len() == 1 && fpairs[0].1 == 1 { 
            return 1;
        }
        return fpairs.iter().fold(0_i128, |p, q| p + n * (q.1 as i128) / (q.0 as i128));
    }
}

fn main() {
    for n in -99..101 {
        print!("{:5}{}", d(n), { if n % 10 == 0 { "\n" } else {""} });
    }
    println!();
    for m in 1..21 {
        println!("(D for 10 ^ {}) divided by 7 is {}", m, d(10_i128.pow(m)) / 7)
    }
}
Output:
  -75  -77   -1 -272  -24  -49  -34  -96  -20 -123
   -1 -140  -32  -45  -22 -124   -1  -43 -108 -176
   -1  -71  -18  -80  -55  -39   -1 -156   -1  -59
  -26  -72   -1  -61  -18 -192  -51  -33   -1  -92
   -1  -31  -22  -92  -16  -81   -1  -56  -20  -45
  -14 -112   -1  -25  -39  -48   -1  -41   -1  -68
  -16  -21   -1  -60  -12  -19  -14  -80   -1  -31
   -1  -32  -27  -15  -10  -44   -1  -13  -10  -24
   -1  -21   -1  -32   -8   -9   -1  -16   -1   -7
   -6  -12   -1   -5   -1   -4   -1   -1    0    0
    0    1    1    4    1    5    1   12    6    7
    1   16    1    9    8   32    1   21    1   24
   10   13    1   44   10   15   27   32    1   31
    1   80   14   19   12   60    1   21   16   68
    1   41    1   48   39   25    1  112   14   45
   20   56    1   81   16   92   22   31    1   92
    1   33   51  192   18   61    1   72   26   59
    1  156    1   39   55   80   18   71    1  176
  108   43    1  124   22   45   32  140    1  123
   20   96   34   49   24  272    1   77   75  140

(D for 10 ^ 1) divided by 7 is 1
(D for 10 ^ 2) divided by 7 is 20
(D for 10 ^ 3) divided by 7 is 300
(D for 10 ^ 4) divided by 7 is 4000
(D for 10 ^ 5) divided by 7 is 50000
(D for 10 ^ 6) divided by 7 is 600000
(D for 10 ^ 7) divided by 7 is 7000000
(D for 10 ^ 8) divided by 7 is 80000000
(D for 10 ^ 9) divided by 7 is 900000000
(D for 10 ^ 10) divided by 7 is 10000000000
(D for 10 ^ 11) divided by 7 is 110000000000
(D for 10 ^ 12) divided by 7 is 1200000000000
(D for 10 ^ 13) divided by 7 is 13000000000000
(D for 10 ^ 14) divided by 7 is 140000000000000
(D for 10 ^ 15) divided by 7 is 1500000000000000
(D for 10 ^ 16) divided by 7 is 16000000000000000
(D for 10 ^ 17) divided by 7 is 170000000000000000
(D for 10 ^ 18) divided by 7 is 1800000000000000000
(D for 10 ^ 19) divided by 7 is 19000000000000000000
(D for 10 ^ 20) divided by 7 is 200000000000000000000

Scala

Translation of: Java
import java.math.BigInteger

object ArithmeticDerivative extends App {

  println("Arithmetic derivatives for -99 to 100 inclusive:")
  for {
    n <- -99 to 100
    column = n + 100
  } print(f"${derivative(BigInteger.valueOf(n))}%4d${if (column % 10 == 0) "\n" else " "}")

  println()

  val seven = BigInteger.valueOf(7)
  for (power <- 1 to 20) {
    println(f"D(10^$power%d) / 7 = ${derivative(BigInteger.TEN.pow(power)).divide(seven)}")
  }

  def derivative(aNumber: BigInteger): BigInteger = {
    if (aNumber.signum == -1) {
      return derivative(aNumber.negate()).negate()
    }
    if (aNumber == BigInteger.ZERO || aNumber == BigInteger.ONE) {
      return BigInteger.ZERO
    }

    var divisor = BigInteger.TWO
    while (divisor.multiply(divisor).compareTo(aNumber) <= 0) {
      if (aNumber.mod(divisor).signum == 0) {
        val quotient = aNumber.divide(divisor)
        return quotient.multiply(derivative(divisor)).add(divisor.multiply(derivative(quotient)))
      }
      divisor = divisor.add(BigInteger.ONE)
    }
    BigInteger.ONE
  }

}
Output:
Arithmetic derivatives for -99 to 100 inclusive:
 -75  -77   -1 -272  -24  -49  -34  -96  -20 -123
  -1 -140  -32  -45  -22 -124   -1  -43 -108 -176
  -1  -71  -18  -80  -55  -39   -1 -156   -1  -59
 -26  -72   -1  -61  -18 -192  -51  -33   -1  -92
  -1  -31  -22  -92  -16  -81   -1  -56  -20  -45
 -14 -112   -1  -25  -39  -48   -1  -41   -1  -68
 -16  -21   -1  -60  -12  -19  -14  -80   -1  -31
  -1  -32  -27  -15  -10  -44   -1  -13  -10  -24
  -1  -21   -1  -32   -8   -9   -1  -16   -1   -7
  -6  -12   -1   -5   -1   -4   -1   -1    0    0
   0    1    1    4    1    5    1   12    6    7
   1   16    1    9    8   32    1   21    1   24
  10   13    1   44   10   15   27   32    1   31
   1   80   14   19   12   60    1   21   16   68
   1   41    1   48   39   25    1  112   14   45
  20   56    1   81   16   92   22   31    1   92
   1   33   51  192   18   61    1   72   26   59
   1  156    1   39   55   80   18   71    1  176
 108   43    1  124   22   45   32  140    1  123
  20   96   34   49   24  272    1   77   75  140

D(10^1) / 7 = 1
D(10^2) / 7 = 20
D(10^3) / 7 = 300
D(10^4) / 7 = 4000
D(10^5) / 7 = 50000
D(10^6) / 7 = 600000
D(10^7) / 7 = 7000000
D(10^8) / 7 = 80000000
D(10^9) / 7 = 900000000
D(10^10) / 7 = 10000000000
D(10^11) / 7 = 110000000000
D(10^12) / 7 = 1200000000000
D(10^13) / 7 = 13000000000000
D(10^14) / 7 = 140000000000000
D(10^15) / 7 = 1500000000000000
D(10^16) / 7 = 16000000000000000
D(10^17) / 7 = 170000000000000000
D(10^18) / 7 = 1800000000000000000
D(10^19) / 7 = 19000000000000000000
D(10^20) / 7 = 200000000000000000000

SETL

program arithmetic_derivative;
    loop for n in [-99..100] do 
        nprint(lpad(str lagarias(n), 6));
        if (col +:= 1) mod 10 = 0 then
            print;
        end if;
    end loop;

    loop for m in [1..20] do
        nprint("D(10^" + lpad(str m, 2) + ") / 7 = ");
        print(lagarias(10**m) div 7);
    end loop; 

    proc lagarias(n);
        return if n<0 then 
            -lagarias(-n)
        elseif n in {0,1} then 
            0
        elseif forall d in {2..floor sqrt n} | n mod d /= 0 then 
            1
        else 
            (n div d)*lagarias(d) + d*lagarias(n div d)
        end;
    end proc;
end program;
Output:
   -75   -77    -1  -272   -24   -49   -34   -96   -20  -123
    -1  -140   -32   -45   -22  -124    -1   -43  -108  -176
    -1   -71   -18   -80   -55   -39    -1  -156    -1   -59
   -26   -72    -1   -61   -18  -192   -51   -33    -1   -92
    -1   -31   -22   -92   -16   -81    -1   -56   -20   -45
   -14  -112    -1   -25   -39   -48    -1   -41    -1   -68
   -16   -21    -1   -60   -12   -19   -14   -80    -1   -31
    -1   -32   -27   -15   -10   -44    -1   -13   -10   -24
    -1   -21    -1   -32    -8    -9    -1   -16    -1    -7
    -6   -12    -1    -5    -1    -4    -1    -1     0     0
     0     1     1     4     1     5     1    12     6     7
     1    16     1     9     8    32     1    21     1    24
    10    13     1    44    10    15    27    32     1    31
     1    80    14    19    12    60     1    21    16    68
     1    41     1    48    39    25     1   112    14    45
    20    56     1    81    16    92    22    31     1    92
     1    33    51   192    18    61     1    72    26    59
     1   156     1    39    55    80    18    71     1   176
   108    43     1   124    22    45    32   140     1   123
    20    96    34    49    24   272     1    77    75   140
D(10^ 1) / 7 = 1
D(10^ 2) / 7 = 20
D(10^ 3) / 7 = 300
D(10^ 4) / 7 = 4000
D(10^ 5) / 7 = 50000
D(10^ 6) / 7 = 600000
D(10^ 7) / 7 = 7000000
D(10^ 8) / 7 = 80000000
D(10^ 9) / 7 = 900000000
D(10^10) / 7 = 10000000000
D(10^11) / 7 = 110000000000
D(10^12) / 7 = 1200000000000
D(10^13) / 7 = 13000000000000
D(10^14) / 7 = 140000000000000
D(10^15) / 7 = 1500000000000000
D(10^16) / 7 = 16000000000000000
D(10^17) / 7 = 170000000000000000
D(10^18) / 7 = 1800000000000000000
D(10^19) / 7 = 19000000000000000000
D(10^20) / 7 = 200000000000000000000

Sidef

Built-in as Number#arithmetic_derivative:

say "Arithmetic derivative for n in range [-99, 100]:"
-99 .. 100 -> map { .arithmetic_derivative }.each_slice(10, {|*a|
    a.map { '%4s' % _ }.join(' ').say
})

say "\nArithmetic derivative D(10^n)/7 for n in range [1, 20]:"
for n in (1..20) {
    say "D(10^#{n})/7 = #{arithmetic_derivative(10**n) / 7}"
}
Output:
Arithmetic derivative for n in range [-99, 100]:
 -75  -77   -1 -272  -24  -49  -34  -96  -20 -123
  -1 -140  -32  -45  -22 -124   -1  -43 -108 -176
  -1  -71  -18  -80  -55  -39   -1 -156   -1  -59
 -26  -72   -1  -61  -18 -192  -51  -33   -1  -92
  -1  -31  -22  -92  -16  -81   -1  -56  -20  -45
 -14 -112   -1  -25  -39  -48   -1  -41   -1  -68
 -16  -21   -1  -60  -12  -19  -14  -80   -1  -31
  -1  -32  -27  -15  -10  -44   -1  -13  -10  -24
  -1  -21   -1  -32   -8   -9   -1  -16   -1   -7
  -6  -12   -1   -5   -1   -4   -1   -1    0    0
   0    1    1    4    1    5    1   12    6    7
   1   16    1    9    8   32    1   21    1   24
  10   13    1   44   10   15   27   32    1   31
   1   80   14   19   12   60    1   21   16   68
   1   41    1   48   39   25    1  112   14   45
  20   56    1   81   16   92   22   31    1   92
   1   33   51  192   18   61    1   72   26   59
   1  156    1   39   55   80   18   71    1  176
 108   43    1  124   22   45   32  140    1  123
  20   96   34   49   24  272    1   77   75  140

Arithmetic derivative D(10^n)/7 for n in range [1, 20]:
D(10^1)/7 = 1
D(10^2)/7 = 20
D(10^3)/7 = 300
D(10^4)/7 = 4000
D(10^5)/7 = 50000
D(10^6)/7 = 600000
D(10^7)/7 = 7000000
D(10^8)/7 = 80000000
D(10^9)/7 = 900000000
D(10^10)/7 = 10000000000
D(10^11)/7 = 110000000000
D(10^12)/7 = 1200000000000
D(10^13)/7 = 13000000000000
D(10^14)/7 = 140000000000000
D(10^15)/7 = 1500000000000000
D(10^16)/7 = 16000000000000000
D(10^17)/7 = 170000000000000000
D(10^18)/7 = 1800000000000000000
D(10^19)/7 = 19000000000000000000
D(10^20)/7 = 200000000000000000000

Explicit implementation:

subset Integer  < Number   { .is_int   }
subset Positive < Integer  { .is_pos   }
subset Negative < Integer  { .is_neg   }
subset Prime    < Positive { .is_prime }

func arithmetic_derivative((0)) { 0 }
func arithmetic_derivative((1)) { 0 }

func arithmetic_derivative(Prime _) { 1 }

func arithmetic_derivative(Negative n) {
    -arithmetic_derivative(-n)
}

func arithmetic_derivative(Positive n) is cached {

    var a = n.factor.rand
    var b = n/a

    arithmetic_derivative(a)*b + a*arithmetic_derivative(b)
}

func arithmetic_derivative(Number n) {
    var (a, b) = n.nude
    (arithmetic_derivative(a)*b - arithmetic_derivative(b)*a) / b**2
}

Wren

Library: Wren-big
Library: Wren-fmt

As integer arithmetic in Wren is inaccurate above 2^53 we need to use BigInt here.

import "./big" for BigInt
import "./fmt" for Fmt

var D = Fn.new { |n|
    if (n < 0) return -D.call(-n)
    if (n < 2) return BigInt.zero
    var f = BigInt.primeFactors(n)
    var c = f.count
    if (c == 1) return BigInt.one
    if (c == 2) return f[0] + f[1]
    var d = n / f[0]
    return D.call(d) * f[0] + d
}

var ad = List.filled(200, 0)
for (n in -99..100) ad[n+99] = D.call(BigInt.new(n))
Fmt.tprint("$4i", ad, 10)
System.print()
for (m in 1..20) {
    Fmt.print("D(10^$-2d) / 7 = $i", m, D.call(BigInt.ten.pow(m))/7)
}
Output:
 -75  -77   -1 -272  -24  -49  -34  -96  -20 -123 
  -1 -140  -32  -45  -22 -124   -1  -43 -108 -176 
  -1  -71  -18  -80  -55  -39   -1 -156   -1  -59 
 -26  -72   -1  -61  -18 -192  -51  -33   -1  -92 
  -1  -31  -22  -92  -16  -81   -1  -56  -20  -45 
 -14 -112   -1  -25  -39  -48   -1  -41   -1  -68 
 -16  -21   -1  -60  -12  -19  -14  -80   -1  -31 
  -1  -32  -27  -15  -10  -44   -1  -13  -10  -24 
  -1  -21   -1  -32   -8   -9   -1  -16   -1   -7 
  -6  -12   -1   -5   -1   -4   -1   -1    0    0 
   0    1    1    4    1    5    1   12    6    7 
   1   16    1    9    8   32    1   21    1   24 
  10   13    1   44   10   15   27   32    1   31 
   1   80   14   19   12   60    1   21   16   68 
   1   41    1   48   39   25    1  112   14   45 
  20   56    1   81   16   92   22   31    1   92 
   1   33   51  192   18   61    1   72   26   59 
   1  156    1   39   55   80   18   71    1  176 
 108   43    1  124   22   45   32  140    1  123 
  20   96   34   49   24  272    1   77   75  140 

D(10^1 ) / 7 = 1
D(10^2 ) / 7 = 20
D(10^3 ) / 7 = 300
D(10^4 ) / 7 = 4000
D(10^5 ) / 7 = 50000
D(10^6 ) / 7 = 600000
D(10^7 ) / 7 = 7000000
D(10^8 ) / 7 = 80000000
D(10^9 ) / 7 = 900000000
D(10^10) / 7 = 10000000000
D(10^11) / 7 = 110000000000
D(10^12) / 7 = 1200000000000
D(10^13) / 7 = 13000000000000
D(10^14) / 7 = 140000000000000
D(10^15) / 7 = 1500000000000000
D(10^16) / 7 = 16000000000000000
D(10^17) / 7 = 170000000000000000
D(10^18) / 7 = 1800000000000000000
D(10^19) / 7 = 19000000000000000000
D(10^20) / 7 = 200000000000000000000

XPL0

Translation of: ALGOL W
function integer Lagarias (N); \Lagarias arithmetic derivative
integer N;
integer F, Q;

        function integer SmallPF (J, K); \Smallest prime factor
        integer J, K;
        return if rem(J/K) = 0 then K else SmallPF(J, K+1);

begin
if N < 0
then return -Lagarias (-N)
else if N = 0 or N = 1
then return 0
else    begin
        F := SmallPF (N, 2);  Q := N / F; 
        return if Q = 1
        then 1
        else Q * Lagarias (F)  +  F * Lagarias (Q)
        end;
end \Lagarias\ ;

integer N;
begin
    for N:= -99 to 100 do begin
        IntOut(0, Lagarias(N) );
        if rem(N/10) = 0 then CrLf(0) else ChOut(0, 9\tab\);
    end;
end
Output:
-75     -77     -1      -272    -24     -49     -34     -96     -20     -123
-1      -140    -32     -45     -22     -124    -1      -43     -108    -176
-1      -71     -18     -80     -55     -39     -1      -156    -1      -59
-26     -72     -1      -61     -18     -192    -51     -33     -1      -92
-1      -31     -22     -92     -16     -81     -1      -56     -20     -45
-14     -112    -1      -25     -39     -48     -1      -41     -1      -68
-16     -21     -1      -60     -12     -19     -14     -80     -1      -31
-1      -32     -27     -15     -10     -44     -1      -13     -10     -24
-1      -21     -1      -32     -8      -9      -1      -16     -1      -7
-6      -12     -1      -5      -1      -4      -1      -1      0       0
0       1       1       4       1       5       1       12      6       7
1       16      1       9       8       32      1       21      1       24
10      13      1       44      10      15      27      32      1       31
1       80      14      19      12      60      1       21      16      68
1       41      1       48      39      25      1       112     14      45
20      56      1       81      16      92      22      31      1       92
1       33      51      192     18      61      1       72      26      59
1       156     1       39      55      80      18      71      1       176
108     43      1       124     22      45      32      140     1       123
20      96      34      49      24      272     1       77      75      140