Padovan sequence

From Rosetta Code
Revision as of 07:36, 19 June 2021 by GordonCharlton (talk | contribs) (Added Quackery.)
Task
Padovan sequence
You are encouraged to solve this task according to the task description, using any language you may know.


The Padovan sequence is similar to the Fibonacci sequence in several ways. Some are given in the table below, and the referenced video shows some of the geometric similarities.

Comment Padovan Fibonacci
Named after. Richard Padovan Leonardo of Pisa: Fibonacci
Recurrence initial values. P(0)=P(1)=P(2)=1 F(0)=0, F(1)=1
Recurrence relation. P(n)=P(n-2)+P(n-3) F(n)=F(n-1)+F(n-2)
First 10 terms. 1,1,1,2,2,3,4,5,7,9 0,1,1,2,3,5,8,13,21,34
Ratio of successive terms... Plastic ratio, p Golden ratio, g
1.324717957244746025960908854… 1.6180339887498948482...
Exact formula of ratios p and q. ((9+69**.5)/18)**(1/3) + ((9-69**.5)/18)**(1/3) (1+5**0.5)/2
Ratio is real root of polynomial. p: x**3-x-1 g: x**2-x-1
Spirally tiling the plane using. Equilateral triangles Squares
Constants for ... s= 1.0453567932525329623 a=5**0.5
... Computing by truncation. P(n)=floor(p**(n-1) / s + .5) F(n)=floor(g**n / a + .5)
L-System Variables. A,B,C A,B
L-System Start/Axiom. A A
L-System Rules. A->B,B->C,C->AB A->B,B->A
Task
  • Write a function/method/subroutine to compute successive members of the Padovan series using the recurrence relation.
  • Write a function/method/subroutine to compute successive members of the Padovan series using the floor function.
  • Show the first twenty terms of the sequence.
  • Confirm that the recurrence and floor based functions give the same results for 64 terms,
  • Write a function/method/... using the L-system to generate successive strings.
  • Show the first 10 strings produced from the L-system
  • Confirm that the length of the first 32 strings produced is the Padovan sequence.

Show output here, on this page.

Ref


ALGOL 68

<lang algol68>BEGIN # show members of the Padovan Sequence calculated in various ways #

   # returns the first n elements of the Padovan sequence by the       #
   #         recurance relation: P(n)=P(n-2)+P(n-3)	                #
   OP PADOVANI = ( INT n )[]INT:
      BEGIN
          [ 0 : n - 1 ]INT p; p[ 0 ] := p[ 1 ] := p[ 2 ] := 1;
          FOR i FROM 3 TO UPB p DO
              p[ i ] := p[ i - 2 ] + p[ i - 3 ]
          OD;
          p
      END; # PADOVANI #
   # returns the first n elements of the Padovan sequence by           #
   #         computing by truncation P(n)=floor(p^(n-1) / s + .5)      #
   #                where s = 1.0453567932525329623                    #
   #                  and p = the "plastic ratio"                      #
   OP PADOVANC = ( INT n )[]INT:
      BEGIN
          LONG REAL    s   = 1.0453567932525329623;
          LONG REAL    p   = 1.324717957244746025960908854;
          LONG REAL    pf := 1 / p;
          [ 0 : n - 1 ]INT result;
          FOR i FROM LWB result TO UPB result DO
              result[ i ] := SHORTEN ENTIER ( pf / s + 0.5 );
              pf         *:= p
          OD;
          result
      END; # PADOVANC #
   # returns the first n L System strings of the Padovan sequence      #
   OP PADOVANL = ( INT n )[]STRING:
      BEGIN
          [ 0 : n - 1 ]STRING l; l[ 0 ] := "A"; l[ 1 ] := "B"; l[ 2 ] := "C";
          FOR i FROM 3 TO UPB l DO
              l[ i ] := l[ i - 3 ] + l[ i - 2 ]
          OD;
          l
   END; # PADOVANC #
   # returns TRUE if a and b have the same values, FALSE otherwise     #
   OP = = ( []INT a, b )BOOL:
      IF LWB a /= LWB b OR UPB a /= UPB b
      THEN # rows are not the same size # FALSE
      ELSE
          BOOL result := TRUE;
          FOR i FROM LWB a TO UPB a WHILE result := a[ i ] = b[ i ] DO SKIP OD;
          result
      FI; # = #
   # returns the number of elements in a                               #
   OP LENGTH = ( []INT a )INT: ( UPB a - LWB a ) + 1;
   # returns the number of characters in s                             #
   OP LENGTH = ( STRING s )INT: ( UPB s - LWB s ) + 1;
   # returns a string representation of n                              #
   OP TOSTRING = ( INT n )STRING: whole( n, 0 );
   # generate 64 elements of the sequence and 32 L System values       #
   []INT    iterative  = PADOVANI 64;
   []INT    calculated = PADOVANC 64;
   []STRING l system   = PADOVANL 32;
   [ LWB l system : UPB l system ]INT l length;
   FOR i FROM LWB l length TO UPB l length DO l length[ i ] := LENGTH l system[ i ] OD;
   # first 20 terms                                                    #
   print( ( "First 20 terms of the Padovan Sequence", newline ) );
   FOR i FROM LWB iterative TO 19 DO
       print( ( " ", TOSTRING iterative[ i ] ) )
   OD;
   print( ( newline ) );
   print( ( "The first "
          , TOSTRING LENGTH iterative
          , " iterative and calculated values "
          , IF iterative = calculated THEN "are the same" ELSE "differ" FI
          , newline
          )
        );
   # print the first 10 values of the L System strings                 #
   print( ( newline, "First 10 L System strings", newline ) );
   FOR i FROM LWB l system TO 9 DO
       print( ( " ", l system[ i ] ) )
   OD;
   print( ( newline ) );
   print( ( "The first "
          , TOSTRING LENGTH l length
          , " iterative values and L System lengths "
          , IF l length = iterative[ LWB l length : UPB l length @ LWB l length ] THEN "are the same" ELSE "differ" FI
          ,  newline
          )
        )

END </lang>

Output:
First 20 terms of the Padovan Sequence
 1 1 1 2 2 3 4 5 7 9 12 16 21 28 37 49 65 86 114 151
The first 64 iterative and calculated values are the same

First 10 L System strings
 A B C AB BC CAB ABBC BCCAB CABABBC ABBCBCCAB
The first 32 iterative values and L System lengths are the same

AppleScript

<lang applescript>--------------------- PADOVAN NUMBERS --------------------

-- padovans :: [Int] on padovans()

   script f
       on |λ|(abc)
           set {a, b, c} to abc
           
           {a, {b, c, a + b}}
       end |λ|
   end script
   
   unfoldr(f, {1, 1, 1})

end padovans


-- padovanFloor :: [Int] on padovanFloor()

   script f
       property p : 1.324717957245
       property s : 1.045356793253
       on |λ|(n)
           {floor(0.5 + ((p ^ (n - 1)) / s)), 1 + n}
       end |λ|
   end script
   
   unfoldr(f, 0)

end padovanFloor


-- padovanLSystem :: [String] on padovanLSystem()

   script rule
       on |λ|(c)
           if "A" = c then
               "B"
           else if "B" = c then
               "C"
           else
               "AB"
           end if
       end |λ|
   end script
   
   script f
       on |λ|(s)
           {s, concatMap(rule, characters of s) as string}
       end |λ|
   end script
   
   unfoldr(f, "A")

end padovanLSystem



TEST -------------------------

on run

   unlines({"First 20 padovans:", ¬
       showList(take(20, padovans())), ¬
       "", ¬
       "The recurrence and floor-based functions", ¬
       "match over the first 64 terms:\n", ¬
       prefixesMatch(padovans(), padovanFloor(), 64), ¬
       "", ¬
       "First 10 L-System strings:", ¬
       showList(take(10, padovanLSystem())), ¬
       "", ¬
       "The lengths of the first 32 L-System", ¬
       "strings match the Padovan sequence:\n", ¬
       prefixesMatch(padovans(), fmap(|length|, padovanLSystem()), 32)})

end run


-- prefixesMatch :: [a] -> [a] -> Bool on prefixesMatch(xs, ys, n)

   take(n, xs) = take(n, ys)

end prefixesMatch



GENERIC ------------------------

-- concatMap :: (a -> [b]) -> [a] -> [b] on concatMap(f, xs)

   set lng to length of xs
   set acc to {}
   tell mReturn(f)
       repeat with i from 1 to lng
           set acc to acc & (|λ|(item i of xs, i, xs))
       end repeat
   end tell
   return acc

end concatMap


-- floor :: Num -> Int on floor(x)

   if class of x is record then
       set nr to properFracRatio(x)
   else
       set nr to properFraction(x)
   end if
   set n to item 1 of nr
   if 0 > item 2 of nr then
       n - 1
   else
       n
   end if

end floor


-- fmap <$> :: (a -> b) -> Gen [a] -> Gen [b] on fmap(f, gen)

   script
       property g : mReturn(f)
       on |λ|()
           set v to gen's |λ|()
           if v is missing value then
               v
           else
               g's |λ|(v)
           end if
       end |λ|
   end script

end fmap


-- intercalate :: String -> [String] -> String on intercalate(delim, xs)

   set {dlm, my text item delimiters} to ¬
       {my text item delimiters, delim}
   set s to xs as text
   set my text item delimiters to dlm
   s

end intercalate


-- length :: [a] -> Int on |length|(xs)

   set c to class of xs
   if list is c or string is c then
       length of xs
   else
       (2 ^ 29 - 1) -- (maxInt - simple proxy for non-finite)
   end if

end |length|


-- map :: (a -> b) -> [a] -> [b] on map(f, xs)

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

end map


-- min :: Ord a => a -> a -> a on min(x, y)

   if y < x then
       y
   else
       x
   end if

end min


-- mReturn :: First-class m => (a -> b) -> m (a -> b) on mReturn(f)

   -- 2nd class handler function lifted into 1st class script wrapper. 
   if script is class of f then
       f
   else
       script
           property |λ| : f
       end script
   end if

end mReturn


-- properFraction :: Real -> (Int, Real) on properFraction(n)

   set i to (n div 1)
   {i, n - i}

end properFraction


-- showList :: [a] -> String on showList(xs)

   "[" & intercalate(",", map(my str, xs)) & "]"

end showList


-- str :: a -> String on str(x)

   x as string

end str


-- take :: Int -> [a] -> [a] -- take :: Int -> String -> String on take(n, xs)

   set c to class of xs
   if list is c then
       if 0 < n then
           items 1 thru min(n, length of xs) of xs
       else
           {}
       end if
   else if string is c then
       if 0 < n then
           text 1 thru min(n, length of xs) of xs
       else
           ""
       end if
   else if script is c then
       set ys to {}
       repeat with i from 1 to n
           set v to |λ|() of xs
           if missing value is v then
               return ys
           else
               set end of ys to v
           end if
       end repeat
       return ys
   else
       missing value
   end if

end take


-- unfoldr :: (b -> Maybe (a, b)) -> b -> [a] on unfoldr(f, v)

   -- A lazy (generator) list unfolded from a seed value
   -- by repeated application of f to a value until no
   -- residue remains. Dual to fold/reduce.
   -- f returns either nothing (missing value),
   -- or just (value, residue).
   script
       property valueResidue : {v, v}
       property g : mReturn(f)
       on |λ|()
           set valueResidue to g's |λ|(item 2 of (valueResidue))
           if missing value ≠ valueResidue then
               item 1 of (valueResidue)
           else
               missing value
           end if
       end |λ|
   end script

end unfoldr


-- unlines :: [String] -> String on unlines(xs)

   -- A single string formed by the intercalation
   -- of a list of strings with the newline character.
   set {dlm, my text item delimiters} to ¬
       {my text item delimiters, linefeed}
   set s to xs as text
   set my text item delimiters to dlm
   s

end unlines</lang>

Output:
First 20 padovans:
[1,1,1,2,2,3,4,5,7,9,12,16,21,28,37,49,65,86,114,151]

The recurrence and floor-based functions
match over the first 64 terms:

true

First 10 L-System strings:
[A,B,C,AB,BC,CAB,ABBC,BCCAB,CABABBC,ABBCBCCAB]

The lengths of the first 32 L-System
strings match the Padovan sequence:

true

C

<lang C>#include <stdio.h>

  1. include <stdlib.h>
  2. include <math.h>
  3. include <string.h>

/* Generate (and memoize) the Padovan sequence using

* the recurrence relationship */

int pRec(int n) {

   static int *memo = NULL;
   static size_t curSize = 0;
   
   /* grow memoization array when necessary and fill with zeroes */
   if (curSize <= (size_t) n) {
       size_t lastSize = curSize;
       while (curSize <= (size_t) n) curSize += 1024 * sizeof(int);
       memo = realloc(memo, curSize * sizeof(int));
       memset(memo + lastSize, 0, (curSize - lastSize) * sizeof(int));
   }
   
   /* if we don't have the value for N yet, calculate it */
   if (memo[n] == 0) {
       if (n<=2) memo[n] = 1;
       else memo[n] = pRec(n-2) + pRec(n-3);
   }
   
   return memo[n];

}

/* Calculate the Nth value of the Padovan sequence

* using the floor function */

int pFloor(int n) {

   long double p = 1.324717957244746025960908854;
   long double s = 1.0453567932525329623;
   return powl(p, n-1)/s + 0.5;

}

/* Given the previous value for the L-system, generate the

* next value */

void nextLSystem(const char *prev, char *buf) {

   while (*prev) {
       switch (*prev++) {
           case 'A': *buf++ = 'B'; break;
           case 'B': *buf++ = 'C'; break;
           case 'C': *buf++ = 'A'; *buf++ = 'B'; break;
       }
   }
   *buf = '\0';

}

int main() {

   // 8192 is enough up to P_33.
   #define BUFSZ 8192
   char buf1[BUFSZ], buf2[BUFSZ];
   int i;
   
   /* Print P_0..P_19 */
   printf("P_0 .. P_19: ");
   for (i=0; i<20; i++) printf("%d ", pRec(i));
   printf("\n");
   
   /* Check that functions match up to P_63 */
   printf("The floor- and recurrence-based functions ");
   for (i=0; i<64; i++) {
       if (pRec(i) != pFloor(i)) {
           printf("do not match at %d: %d != %d.\n",
               i, pRec(i), pFloor(i));
           break;
       }
   }
   if (i == 64) {
       printf("match from P_0 to P_63.\n");
   }
   
   /* Show first 10 L-system strings */
   printf("\nThe first 10 L-system strings are:\n"); 
   for (strcpy(buf1, "A"), i=0; i<10; i++) {
       printf("%s\n", buf1);
       strcpy(buf2, buf1);
       nextLSystem(buf2, buf1);
   }
   
   /* Check lengths of strings against pFloor up to P_31 */
   printf("\nThe floor- and L-system-based functions ");
   for (strcpy(buf1, "A"), i=0; i<32; i++) {
       if ((int)strlen(buf1) != pFloor(i)) {
           printf("do not match at %d: %d != %d\n",
               i, (int)strlen(buf1), pFloor(i));
           break;
       }
       strcpy(buf2, buf1);
       nextLSystem(buf2, buf1);
   }
   if (i == 32) {
       printf("match from P_0 to P_31.\n");
   }
   
   return 0;

}</lang>

Output:
P_0 .. P_19: 1 1 1 2 2 3 4 5 7 9 12 16 21 28 37 49 65 86 114 151
The floor- and recurrence-based functions match from P_0 to P_63.

The first 10 L-system strings are:
A
B
C
AB
BC
CAB
ABBC
BCCAB
CABABBC
ABBCBCCAB

The floor- and L-system-based functions match from P_0 to P_31.

C++

<lang cpp>#include <iostream>

  1. include <map>
  2. include <cmath>

// Generate the Padovan sequence using the recurrence // relationship. int pRec(int n) {

   static std::map<int,int> memo;
   auto it = memo.find(n);
   if (it != memo.end()) return it->second;
   if (n <= 2) memo[n] = 1;
   else memo[n] = pRec(n-2) + pRec(n-3);
   return memo[n];

}

// Calculate the N'th Padovan sequence using the // floor function. int pFloor(int n) {

   long const double p = 1.324717957244746025960908854;
   long const double s = 1.0453567932525329623;
   return std::pow(p, n-1)/s + 0.5;

}

// Return the N'th L-system string std::string& lSystem(int n) {

   static std::map<int,std::string> memo;
   auto it = memo.find(n);
   if (it != memo.end()) return it->second;
   
   if (n == 0) memo[n] = "A";
   else {
       memo[n] = "";
       for (char ch : memo[n-1]) {
           switch(ch) {
               case 'A': memo[n].push_back('B'); break;
               case 'B': memo[n].push_back('C'); break;
               case 'C': memo[n].append("AB"); break;
           }
       }
   }
   return memo[n];

}

// Compare two functions up to p_N using pFn = int(*)(int); void compare(pFn f1, pFn f2, const char* descr, int stop) {

   std::cout << "The " << descr << " functions ";
   int i;
   for (i=0; i<stop; i++) {
       int n1 = f1(i);
       int n2 = f2(i);
       if (n1 != n2) {
           std::cout << "do not match at " << i
                     << ": " << n1 << " != " << n2 << ".\n";
           break;
       }
   }
   if (i == stop) {
       std::cout << "match from P_0 to P_" << stop << ".\n";
   }

}

int main() {

   /* Print P_0 to P_19 */
   std::cout << "P_0 .. P_19: ";
   for (int i=0; i<20; i++) std::cout << pRec(i) << " ";
   std::cout << "\n";
   
   /* Check that floor and recurrence match up to P_64 */
   compare(pFloor, pRec, "floor- and recurrence-based", 64);
   
   /* Show first 10 L-system strings */
   std::cout << "\nThe first 10 L-system strings are:\n";
   for (int i=0; i<10; i++) std::cout << lSystem(i) << "\n";
   std::cout << "\n";
   
   /* Check lengths of strings against pFloor up to P_31 */
   compare(pFloor, [](int n){return (int)lSystem(n).length();}, 
                           "floor- and L-system-based", 32);
   return 0;

}</lang>

Output:
P_0 .. P_19: 1 1 1 2 2 3 4 5 7 9 12 16 21 28 37 49 65 86 114 151
The floor- and recurrence-based functions match from P_0 to P_64.

The first 10 L-system strings are:
A
B
C
AB
BC
CAB
ABBC
BCCAB
CABABBC
ABBCBCCAB

The floor- and L-system-based functions match from P_0 to P_32.

Clojure

<lang clojure>(def padovan (map first (iterate (fn a b c [b c (+ a b)]) [1 1 1])))

(def pad-floor

 (let [p 1.324717957244746025960908854
       s 1.0453567932525329623]
   (map (fn [n] (int (Math/floor (+ (/ (Math/pow p (dec n)) s) 0.5)))) (range))))

(def pad-l

 (iterate (fn f c & s
            (case c
              \A (str "B" (f s))
              \B (str "C" (f s))
              \C (str "AB" (f s))
              (str "")))
          "A"))

(defn comp-seq [n seqa seqb]

 (= (take n seqa) (take n seqb)))

(defn comp-all [n]

 (= (map count (vec (take n pad-l)))
    (take n padovan)
    (take n pad-floor)))

(defn padovan-print [& args]

 ((print "The first 20 items with recursion relation are: ")
  (println (take 20 padovan))
  (println)
  (println (str
            "The recurrence and floor based algorithms "
            (if (comp-seq 64 padovan pad-floor) "match" "not match")
            " to n=64"))
  (println)
  (println "The first 10 L-system strings are:")
  (println (take 10 pad-l))
  (println)
  (println (str
            "The L-system, recurrence and floor based algorithms "
            (if (comp-all 32) "match" "not match")
            " to n=32"))))</lang>
Output:
The first 20 items with recursion relation are: (1 1 1 2 2 3 4 5 7 9 12 16 21 28 37 49 65 86 114 151)

The recurrence and floor based algorithms match to n=64

The first 10 L-system strings are:
(A B C AB BC CAB ABBC BCCAB CABABBC ABBCBCCAB)

The L-system, recurrence and floor based algorithms match to n=32

Delphi

Translation of: C++

Thanks Rudy Velthuis for the Velthuis.BigDecimals library.
Boost.Generics.Collection is part of DelphiBoostLib. <lang Delphi> program Padovan_sequence;

{$APPTYPE CONSOLE}

uses

 System.SysUtils,
 Velthuis.BigDecimals,
 Boost.Generics.Collection;

type

 TpFn = TFunc<Integer, Integer>;

var

 RecMemo: TDictionary<Integer, Integer>;
 lSystemMemo: TDictionary<Integer, string>;

function pRec(n: Integer): Integer; begin

 if RecMemo.HasKey(n) then
   exit(RecMemo[n]);
 if (n <= 2) then
   RecMemo[n] := 1
 else
   RecMemo[n] := pRec(n - 2) + pRec(n - 3);
 Result := RecMemo[n];

end;

function pFloor(n: Integer): Integer; var

 p, s, a: BigDecimal;

begin

 p := '1.324717957244746025960908854';
 s := '1.0453567932525329623';
 a := p.IntPower(n - 1, 64);
 Result := Round(BigDecimal.Divide(a, s));

end;

function lSystem(n: Integer): string; begin

 if n = 0 then
   lSystemMemo[n] := 'A'
 else
 begin
   lSystemMemo[n] := ;
   for var ch in lSystemMemo[n - 1] do
   begin
     case ch of
       'A':
         lSystemMemo[n] := lSystemMemo[n] + 'B';
       'B':
         lSystemMemo[n] := lSystemMemo[n] + 'C';
       'C':
         lSystemMemo[n] := lSystemMemo[n] + 'AB';
     end;
   end;
 end;
 Result := lSystemMemo[n];

end;

procedure Compare(f1, f2: TpFn; descr: string; stop: Integer); begin

 write('The ', descr, ' functions ');
 var i := 0;
 while i < stop do
 begin
   var n1 := f1(i);
   var n2 := f2(i);
   if n1 <> n2 then
   begin
     write('do not match at ', i);
     writeln(': ', n1, ' != ', n2, '.');
     break;
   end;
   inc(i);
 end;
 if i = stop then
   writeln('match from P_0 to P_', stop, '.');

end;

begin

 RecMemo := TDictionary<Integer, Integer>.Create([], []);
 lSystemMemo := TDictionary<Integer, string>.Create([], []);
 write('P_0 .. P_19: ');
 for var i := 0 to 19 do
   write(pRec(i), ' ');
 writeln;
 Compare(pFloor, pRec, 'floor- and recurrence-based', 64);
 writeln(#10'The first 10 L-system strings are:');
 for var i := 0 to 9 do
   writeln(lSystem(i));
 writeln;
 Compare(pFloor,
   function(n: Integer): Integer
   begin
     Result := length(lSystem(n));
   end, 'floor- and L-system-based', 32);
 readln;

end.</lang>

Factor

Works with: Factor version 0.99 2021-02-05

<lang factor>USING: L-system accessors io kernel make math math.functions memoize prettyprint qw sequences ;

CONSTANT: p 1.324717957244746025960908854 CONSTANT: s 1.0453567932525329623

pfloor ( m -- n ) 1 - p swap ^ s /f .5 + >integer ;

MEMO: precur ( m -- n )

   dup 3 < [ drop 1 ]
   [ [ 2 - precur ] [ 3 - precur ] bi + ] if ;
plsys, ( L-system -- )
   [ iterate-L-system-string ] [ string>> , ] bi ;
plsys ( n -- seq )
   <L-system>
   "A" >>axiom
   { qw{ A B } qw{ B C } qw{ C AB } } >>rules
   swap 1 - '[ "A" , _ [ dup plsys, ] times ] { } make nip ;

"First 20 terms of the Padovan sequence:" print 20 [ pfloor pprint bl ] each-integer nl nl

64 [ [ pfloor ] [ precur ] bi assert= ] each-integer "Recurrence and floor based algorithms match to n=63." print nl

"First 10 L-system strings:" print 10 plsys . nl

32 <iota> [ pfloor ] map 32 plsys [ length ] map assert= "The L-system, recurrence and floor based algorithms match to n=31." print</lang>

Output:
First 20 terms of the Padovan sequence:
1 1 1 2 2 3 4 5 7 9 12 16 21 28 37 49 65 86 114 151 

Recurrence and floor based algorithms match to n=63.

First 10 L-system strings:
{
    "A"
    "B"
    "C"
    "AB"
    "BC"
    "CAB"
    "ABBC"
    "BCCAB"
    "CABABBC"
    "ABBCBCCAB"
}

The L-system, recurrence and floor based algorithms match to n=31.

Go

Translation of: Wren

<lang go>package main

import (

   "fmt"
   "math"
   "math/big"
   "strings"

)

func padovanRecur(n int) []int {

   p := make([]int, n)
   p[0], p[1], p[2] = 1, 1, 1
   for i := 3; i < n; i++ {
       p[i] = p[i-2] + p[i-3]
   }
   return p

}

func padovanFloor(n int) []int {

   var p, s, t, u = new(big.Rat), new(big.Rat), new(big.Rat), new(big.Rat)
   p, _ = p.SetString("1.324717957244746025960908854")
   s, _ = s.SetString("1.0453567932525329623")
   f := make([]int, n)
   pow := new(big.Rat).SetInt64(1)
   u = u.SetFrac64(1, 2)
   t.Quo(pow, p)
   t.Quo(t, s)
   t.Add(t, u)
   v, _ := t.Float64()
   f[0] = int(math.Floor(v))
   for i := 1; i < n; i++ {
       t.Quo(pow, s)
       t.Add(t, u)
       v, _ = t.Float64()
       f[i] = int(math.Floor(v))
       pow.Mul(pow, p)
   }
   return f

}

type LSystem struct {

   rules         map[string]string
   init, current string

}

func step(lsys *LSystem) string {

   var sb strings.Builder
   if lsys.current == "" {
       lsys.current = lsys.init
   } else {
       for _, c := range lsys.current {
           sb.WriteString(lsys.rules[string(c)])
       }
       lsys.current = sb.String()
   }
   return lsys.current

}

func padovanLSys(n int) []string {

   rules := map[string]string{"A": "B", "B": "C", "C": "AB"}
   lsys := &LSystem{rules, "A", ""}
   p := make([]string, n)
   for i := 0; i < n; i++ {
       p[i] = step(lsys)
   }
   return p

}

// assumes lists are same length func areSame(l1, l2 []int) bool {

   for i := 0; i < len(l1); i++ {
       if l1[i] != l2[i] {
           return false
       }
   }
   return true

}

func main() {

   fmt.Println("First 20 members of the Padovan sequence:")
   fmt.Println(padovanRecur(20))
   recur := padovanRecur(64)
   floor := padovanFloor(64)
   same := areSame(recur, floor)
   s := "give"
   if !same {
       s = "do not give"
   }
   fmt.Println("\nThe recurrence and floor based functions", s, "the same results for 64 terms.")
   p := padovanLSys(32)
   lsyst := make([]int, 32)
   for i := 0; i < 32; i++ {
       lsyst[i] = len(p[i])
   }
   fmt.Println("\nFirst 10 members of the Padovan L-System:")
   fmt.Println(p[:10])
   fmt.Println("\nand their lengths:")
   fmt.Println(lsyst[:10])
   same = areSame(recur[:32], lsyst)
   s = "give"
   if !same {
       s = "do not give"
   }
   fmt.Println("\nThe recurrence and L-system based functions", s, "the same results for 32 terms.")

</lang>

Output:
First 20 members of the Padovan sequence:
[1 1 1 2 2 3 4 5 7 9 12 16 21 28 37 49 65 86 114 151]

The recurrence and floor based functions give the same results for 64 terms.

First 10 members of the Padovan L-System:
[A B C AB BC CAB ABBC BCCAB CABABBC ABBCBCCAB]

and their lengths:
[1 1 1 2 2 3 4 5 7 9]

The recurrence and L-system based functions give the same results for 32 terms.

Haskell

<lang haskell>-- list of Padovan numbers using recurrence pRec = map (\(a,_,_) -> a) $ iterate (\(a,b,c) -> (b,c,a+b)) (1,1,1)

-- list of Padovan numbers using self-referential lazy lists pSelfRef = 1 : 1 : 1 : zipWith (+) pSelfRef (tail pSelfRef)

-- list of Padovan numbers generated from floor function pFloor = map f [0..]

   where f n = floor $ p**fromInteger (pred n) / s + 0.5
         p   = 1.324717957244746025960908854 
         s   = 1.0453567932525329623
         

-- list of L-system strings lSystem = iterate f "A"

   where f []      = []
         f ('A':s) = 'B':f s
         f ('B':s) = 'C':f s
         f ('C':s) = 'A':'B':f s

-- check if first N elements match checkN n as bs = take n as == take n bs

main = do

   putStr "P_0 .. P_19: "
   putStrLn $ unwords $ map show $ take 20 pRec
   
   putStr "The floor- and recurrence-based functions "
   putStr $ if checkN 64 pRec pFloor then "match" else "do not match"
   putStr " from P_0 to P_63.\n"
   putStr "The self-referential- and recurrence-based functions "
   putStr $ if checkN 64 pRec pSelfRef then "match" else "do not match"
   putStr " from P_0 to P_63.\n\n"
       
   putStr "The first 10 L-system strings are:\n"
   putStrLn $ unwords $ take 10 lSystem
   
   putStr "\nThe floor- and L-system-based functions "
   putStr $ if checkN 32 pFloor (map length lSystem) 
            then "match" else "do not match"
   putStr " from P_0 to P_31.\n"</lang>
Output:
P_0 .. P_19: 1 1 1 2 2 3 4 5 7 9 12 16 21 28 37 49 65 86 114 151
The floor- and recurrence-based functions match from P_0 to P_63.
The self-referential- and recurrence-based functions match from P_0 to P_63.

The first 10 L-system strings are:
A B C AB BC CAB ABBC BCCAB CABABBC ABBCBCCAB

The floor- and L-system-based functions match from P_0 to P_31.


and a variant expressed in terms of unfoldr, which allows for a coherent treatment of these three cases – isolating the respects in which they differ – and also lends itself to a simple translation to the N-Step Padovan case, covered in another task. <lang haskell>import Data.List (unfoldr)


PADOVAN NUMBERS --------------------

padovans :: [Integer] padovans = unfoldr f (1, 1, 1)

 where
   f (a, b, c) = Just (a, (b, c, a + b))


padovanFloor :: [Integer] padovanFloor = unfoldr f 0

 where
   f = Just . (((,) . g) <*> succ)
   g = floor . (0.5 +) . (/ s) . (p **) . fromInteger . pred
   p = 1.324717957244746025960908854
   s = 1.0453567932525329623


padovanLSystem :: [String] padovanLSystem = unfoldr f "A"

 where
   f = Just . ((,) <*> concatMap rule)
   rule 'A' = "B"
   rule 'B' = "C"
   rule 'C' = "AB"



TESTS -------------------------

main :: IO () main =

 mapM_
   putStrLn
   [ "First 20 padovans:\n",
     show $ take 20 padovans,
     [],
     "The recurrence and floor based functions",
     "match over 64 terms:\n",
     show $ prefixesMatch padovans padovanFloor 64,
     [],
     "First 10 L-System strings:\n",
     show $ take 10 padovanLSystem,
     [],
     "The length of the first 32 strings produced",
     "is the Padovan sequence:\n",
     show $
       prefixesMatch
         padovans
         (fromIntegral . length <$> padovanLSystem)
         32
   ]

prefixesMatch :: Eq a => [a] -> [a] -> Int -> Bool prefixesMatch xs ys n = and (zipWith (==) (take n xs) ys)</lang>

Output:
First 20 padovans:

[1,1,1,2,2,3,4,5,7,9,12,16,21,28,37,49,65,86,114,151]

The recurrence and floor based functions
match over 64 terms:

True

First 10 L-System strings:

["A","B","C","AB","BC","CAB","ABBC","BCCAB","CABABBC","ABBCBCCAB"]

The length of the first 32 strings produced
is the Padovan sequence:

True

J

Implementation: <lang J> padovanSeq=: (],+/@(_2 _3{]))^:([-3:)&1 1 1

realRoot=. {:@(#~ ]=|)@;@p. padovanNth=: 0.5 <.@+ (realRoot _23 23 _2 1) %~ (realRoot _1 _1 0 1)^<:

padovanL=: rplc&('A';'B'; 'B';'C'; 'C';'AB')@]^:[&'A' seqLen=. #@(-.&' ')"1 </lang>

Typically, inductive sequences based on a function F with an initial value G can be expressed using an expression of the form F@]^:[@G or something similar. Here, [ represents the argument to the derived recurrence function. For padovanSeq, we are generating a sequence, so we want to retain the previous values. So instead of just using f=: +/@(_2 3{]) which adds up the second and third numbers from the end of the sequence, we also retain the previous values using F=: ],f

But, also, since our initial value is a sequence with three elements, we can make the argument to the recurrence function be the length of the desired sequence by replacing [ for the repetition count with [-3:

Task examples:

<lang J>

  padovanSeq 20

1 1 1 2 2 3 4 5 7 9 12 16 21 28 37 49 65 86 114 151

  (padovanSeq 64) -: padovanNth(i.64)

1

  padovanL i.10

A B C AB BC CAB ABBC BCCAB CABABBC ABBCBCCAB

  (padovanSeq 32) -: seqLen padovanL i.32

1 </lang>

JavaScript

<lang javascript>(() => {

   "use strict";
   // ----------------- PADOVAN NUMBERS -----------------
   // padovans :: [Int]
   const padovans = () => {
       // Non-finite series of Padovan numbers,
       // defined in terms of recurrence relations.
       const f = ([a, b, c]) => [
           a,
           [b, c, a + b]
       ];
       return unfoldr(f)([1, 1, 1]);
   };


   // padovanFloor :: [Int]
   const padovanFloor = () => {
       // The Padovan series, defined in terms
       // of a floor function.
       const
           // NB JavaScript loses some of this
           // precision at run-time.
           p = 1.324717957244746025960908854,
           s = 1.0453567932525329623;
       const f = n => [
           Math.floor(((p ** (n - 1)) / s) + 0.5),
           1 + n
       ];
       return unfoldr(f)(0);
   };


   // padovanLSystem : [Int]
   const padovanLSystem = () => {
       // An L-system generating terms whose lengths
       // are the values of the Padovan integer series.
       const rule = c =>
           "A" === c ? (
               "B"
           ) : "B" === c ? (
               "C"
           ) : "AB";
       const f = s => [
           s,
           chars(s).flatMap(rule)
           .join("")
       ];
       return unfoldr(f)("A");
   };


   // ---------------------- TEST -----------------------
   // main :: IO ()
   const main = () => {
       // prefixesMatch :: [a] -> [a] -> Bool
       const prefixesMatch = xs =>
           ys => n => and(
               zipWith(a => b => a === b)(
                   take(n)(xs)
               )(
                   take(n)(ys)
               )
           );
       return [
               "First 20 padovans:",
               take(20)(padovans()),
               "\nThe recurrence and floor-based functions",
               "match over the first 64 terms:\n",
               prefixesMatch(
                   padovans()
               )(
                   padovanFloor()
               )(64),
               "\nFirst 10 L-System strings:",
               take(10)(padovanLSystem()),
               "\nThe lengths of the first 32 L-System",
               "strings match the Padovan sequence:\n",
               prefixesMatch(
                   padovans()
               )(
                   fmap(length)(padovanLSystem())
               )(32)
           ]
           .map(str)
           .join("\n");
   };
   // --------------------- GENERIC ---------------------
   // and :: [Bool] -> Bool
   const and = xs =>
       // True unless any value in xs is false.
       [...xs].every(Boolean);


   // chars :: String -> [Char]
   const chars = s =>
       s.split("");


   // fmap <$> :: (a -> b) -> Gen [a] -> Gen [b]
   const fmap = f =>
       function* (gen) {
           let v = take(1)(gen);
           while (0 < v.length) {
               yield f(v[0]);
               v = take(1)(gen);
           }
       };


   // length :: [a] -> Int
   const length = xs =>
       // Returns Infinity over objects without finite
       // length. This enables zip and zipWith to choose
       // the shorter argument when one is non-finite,
       // like cycle, repeat etc
       "GeneratorFunction" !== xs.constructor
       .constructor.name ? (
           xs.length
       ) : Infinity;


   // take :: Int -> [a] -> [a]
   // take :: Int -> String -> String
   const take = n =>
       // The first n elements of a list,
       // string of characters, or stream.
       xs => "GeneratorFunction" !== xs
       .constructor.constructor.name ? (
           xs.slice(0, n)
       ) : [].concat(...Array.from({
           length: n
       }, () => {
           const x = xs.next();
           return x.done ? [] : [x.value];
       }));


   // str :: a -> String
   const str = x =>
       "string" !== typeof x ? (
           JSON.stringify(x)
       ) : x;


   // unfoldr :: (b -> Maybe (a, b)) -> b -> Gen [a]
   const unfoldr = f =>
       // A lazy (generator) list unfolded from a seed value
       // by repeated application of f to a value until no
       // residue remains. Dual to fold/reduce.
       // f returns either Null or just (value, residue).
       // For a strict output list,
       // wrap with `list` or Array.from
       x => (
           function* () {
               let valueResidue = f(x);
               while (null !== valueResidue) {
                   yield valueResidue[0];
                   valueResidue = f(valueResidue[1]);
               }
           }()
       );


   // zipWithList :: (a -> b -> c) -> [a] -> [b] -> [c]
   const zipWith = f =>
       // A list constructed by zipping with a
       // custom function, rather than with the
       // default tuple constructor.
       xs => ys => ((xs_, ys_) => {
           const lng = Math.min(length(xs_), length(ys_));
           return take(lng)(xs_).map(
               (x, i) => f(x)(ys_[i])
           );
       })([...xs], [...ys]);
   // MAIN ---
   return main();

})();</lang>

Output:
First 20 padovans:
[1,1,1,2,2,3,4,5,7,9,12,16,21,28,37,49,65,86,114,151]

The recurrence and floor-based functions
match over the first 64 terms:

true

First 10 L-System strings:
["A","B","C","AB","BC","CAB","ABBC","BCCAB","CABABBC","ABBCBCCAB"]

The lengths of the first 32 L-System
strings match the Padovan sequence:

true

Julia

<lang julia>""" Recursive Padowan """ rPadovan(n) = (n < 4) ? one(n) : rPadovan(n - 3) + rPadovan(n - 2)

""" Floor function calculation Padowan """ function fPadovan(n)::Int

   p, s = big"1.324717957244746025960908854", big"1.0453567932525329623"
   return Int(floor(p^(n-2) / s + .5))

end

""" LSystem Padowan """ function list_LsysPadowan(N)

   rules = Dict("A" => "B", "B" => "C", "C" => "AB")
   seq, lens = ["A"], [1]
   for i in 1:N
       str = prod([rules[string(c)] for c in seq[end]])
       push!(seq, str)
       push!(lens, length(str))
   end
   return seq, lens

end

const lr, lf = [rPadovan(i) for i in 1:64], [fPadovan(i) for i in 1:64] const sL, lL = list_LsysPadowan(32) println("N Recursive Floor LSystem String\n=============================================") foreach(i -> println(rpad(i, 4), rpad(lr[i], 12), rpad(lf[i], 12),

   rpad(i < 33 ? lL[i] : "", 12), (i < 11 ? sL[i] : "")), 1:64)

</lang>

Output:
N  Recursive  Floor      LSystem      String
=============================================
1   1           1           1           A
2   1           1           1           B
3   1           1           1           C
4   2           2           2           AB
5   2           2           2           BC
6   3           3           3           CAB
7   4           4           4           ABBC
8   5           5           5           BCCAB
9   7           7           7           CABABBC
10  9           9           9           ABBCBCCAB
11  12          12          12
12  16          16          16
13  21          21          21
14  28          28          28
15  37          37          37
16  49          49          49
17  65          65          65
18  86          86          86
19  114         114         114
20  151         151         151
21  200         200         200
22  265         265         265
23  351         351         351
24  465         465         465
25  616         616         616
26  816         816         816
27  1081        1081        1081
28  1432        1432        1432
29  1897        1897        1897
30  2513        2513        2513
31  3329        3329        3329
32  4410        4410        4410
33  5842        5842
34  7739        7739
35  10252       10252
36  13581       13581
37  17991       17991
38  23833       23833
39  31572       31572
40  41824       41824
41  55405       55405
42  73396       73396
43  97229       97229
44  128801      128801
45  170625      170625
46  226030      226030
47  299426      299426
48  396655      396655
49  525456      525456
50  696081      696081
51  922111      922111
52  1221537     1221537
53  1618192     1618192
54  2143648     2143648
55  2839729     2839729
56  3761840     3761840
57  4983377     4983377
58  6601569     6601569
59  8745217     8745217
60  11584946    11584946
61  15346786    15346786
62  20330163    20330163
63  26931732    26931732
64  35676949    35676949

Mathematica / Wolfram Language

<lang Mathematica>ClearAll[Padovan1,a,p,s] p=N[Surd[((9+Sqrt[69])/18),3]+Surd[((9-Sqrt[69])/18),3],200]; s=1.0453567932525329623; Padovan1[nmax_Integer]:=RecurrenceTable[{a[n+1]==a[n-1]+a[n-2],a[0]==1,a[1]==1,a[2]==1},a,{n,0,nmax-1}] Padovan2[nmax_Integer]:=With[{},Floor[p^Range[-1,nmax-2]/s+1/2]] Padovan1[20] Padovan2[20] Padovan1[64]===Padovan2[64] SubstitutionSystem[{"A"->"B","B"->"C","C"->"AB"},"A",10]//Column (StringLength/@SubstitutionSystem[{"A"->"B","B"->"C","C"->"AB"},"A",31])==Padovan2[32]</lang>

Output:
{1,1,1,2,2,3,4,5,7,9,12,16,21,28,37,49,65,86,114,151}
{1,1,1,2,2,3,4,5,7,9,12,16,21,28,37,49,65,86,114,151}
True
A
B
C
AB
BC
CAB
ABBC
BCCAB
CABABBC
ABBCBCCAB
BCCABCABABBC
True

Nim

<lang Nim>import sequtils, strutils, tables

const

 P = 1.324717957244746025960908854
 S = 1.0453567932525329623
 Rules = {'A': "B", 'B': "C", 'C': "AB"}.toTable


iterator padovan1(n: Natural): int {.closure.} =

 ## Yield the first "n" Padovan values using recurrence relation.
 for _ in 1..min(n, 3): yield 1
 var a, b, c = 1
 var count = 3
 while count < n:
   (a, b, c) = (b, c, a + b)
   yield c
   inc count


iterator padovan2(n: Natural): int {.closure.} =

 ## Yield the first "n" Padovan values using formula.
 if n > 1: yield 1
 var p = 1.0
 var count = 1
 while count < n:
   yield (p / S).toInt
   p *= P
   inc count


iterator padovan3(n: Natural): string {.closure.} =

 ## Yield the strings produced by the L-system.
 var s = "A"
 var count = 0
 while count < n:
   yield s
   var next: string
   for ch in s:
     next.add Rules[ch]
   s = move(next)
   inc count


echo "First 20 terms of the Padovan sequence:" echo toSeq(padovan1(20)).join(" ")

let list1 = toSeq(padovan1(64)) let list2 = toSeq(padovan2(64)) echo "The first 64 iterative and calculated values ",

    if list1 == list2: "are the same." else: "differ."

echo "" echo "First 10 L-system strings:" echo toSeq(padovan3(10)).join(" ") echo "" echo "Lengths of the 32 first L-system strings:" let list3 = toSeq(padovan3(32)).mapIt(it.len) echo list3.join(" ") echo "These lengths are",

    if list3 == list1[0..31]: " " else: " not ",
    "the 32 first terms of the Padovan sequence."</lang>
Output:
First 20 terms of the Padovan sequence:
1 1 1 2 2 3 4 5 7 9 12 16 21 28 37 49 65 86 114 151
The first 64 iterative and calculated values are the same.

First 10 L-system strings:
A B C AB BC CAB ABBC BCCAB CABABBC ABBCBCCAB

Lengths of the 32 first L-system strings:
1 1 1 2 2 3 4 5 7 9 12 16 21 28 37 49 65 86 114 151 200 265 351 465 616 816 1081 1432 1897 2513 3329 4410
These lengths are the 32 first terms of the Padovan sequence.

Perl

Translation of: Raku

<lang perl>use strict; use warnings; use feature <state say>; use List::Lazy 'lazy_list';

my $p = 1.32471795724474602596; my $s = 1.0453567932525329623; my %rules = (A => 'B', B => 'C', C => 'AB');

my $pad_recur = lazy_list { state @p = (1, 1, 1, 2); push @p, $p[1]+$p[2]; shift @p };

sub pad_floor { int 1/2 + $p**($_<3 ? 1 : $_-2) / $s }

my($l, $m, $n) = (10, 20, 32);

my(@pr, @pf); push @pr, $pad_recur->next() for 1 .. $n; say join ' ', @pr[0 .. $m-1]; push @pf, pad_floor($_) for 1 .. $n; say join ' ', @pf[0 .. $m-1];

my @L = 'A'; push @L, join , @rules{split , $L[-1]} for 1 .. $n; say join ' ', @L[0 .. $l-1];

$pr[$_] == $pf[$_] and $pr[$_] == length $L[$_] or die "Uh oh, n=$_: $pr[$_] vs $pf[$_] vs " . length $L[$_] for 0 .. $n-1; say '100% agreement among all 3 methods.';</lang>

Output:
1 1 1 2 2 3 4 5 7 9 12 16 21 28 37 49 65 86 114 151
1 1 1 2 2 3 4 5 7 9 12 16 21 28 37 49 65 86 114 151
A B C AB BC CAB ABBC BCCAB CABABBC ABBCBCCAB
100% agreement among all 3 methods.

Phix

<lang Phix>sequence padovan = {1,1,1} function padovanr(integer n)

   while length(padovan)<n do
       padovan &= padovan[$-2]+padovan[$-1]
   end while
   return padovan[n]

end function

constant p = 1.324717957244746025960908854,

        s = 1.0453567932525329623 

function padovana(integer n)

   return floor(power(p,n-2)/s + 0.5)

end function

constant l = {"B","C","AB"} function padovanl(string prev)

   string res = ""
   for i=1 to length(prev) do
       res &= l[prev[i]-64]
   end for
   return res

end function

sequence pl = "A", l10 = {} for n=1 to 64 do

   integer pn = padovanr(n)
   if padovana(n)!=pn or length(pl)!=pn then crash("oops") end if
   if n<=10 then l10 = append(l10,pl) end if
   pl = padovanl(pl) 

end for printf(1,"The first 20 terms of the Padovan sequence: %v\n\n",{padovan[1..20]}) printf(1,"The first 10 L-system strings: %v\n\n",{l10}) printf(1,"recursive, algorithmic, and l-system agree to n=64\n")</lang>

Output:
The first 20 terms of the Padovan sequence: {1,1,1,2,2,3,4,5,7,9,12,16,21,28,37,49,65,86,114,151}

The first 10 L-system strings: {"A","B","C","AB","BC","CAB","ABBC","BCCAB","CABABBC","ABBCBCCAB"}

recursive, algorithmic, and l-system agree to n=64

Python

Python: Idiomatic

<lang python>from math import floor from collections import deque from typing import Dict, Generator


def padovan_r() -> Generator[int, None, None]:

   last = deque([1, 1, 1], 4)
   while True:
       last.append(last[-2] + last[-3])
       yield last.popleft()

_p, _s = 1.324717957244746025960908854, 1.0453567932525329623

def padovan_f(n: int) -> int:

   return floor(_p**(n-1) / _s + .5)

def padovan_l(start: str='A',

            rules: Dict[str, str]=dict(A='B', B='C', C='AB')
            ) -> Generator[str, None, None]:
   axiom = start
   while True:
       yield axiom
       axiom = .join(rules[ch] for ch in axiom)


if __name__ == "__main__":

   from itertools import islice
   print("The first twenty terms of the sequence.")
   print(str([padovan_f(n) for n in range(20)])[1:-1])
   r_generator = padovan_r()
   if all(next(r_generator) == padovan_f(n) for n in range(64)):
       print("\nThe recurrence and floor based algorithms match to n=63 .")
   else:
       print("\nThe recurrence and floor based algorithms DIFFER!")
   print("\nThe first 10 L-system string-lengths and strings")
   l_generator = padovan_l(start='A', rules=dict(A='B', B='C', C='AB'))
   print('\n'.join(f"  {len(string):3} {repr(string)}"
                   for string in islice(l_generator, 10)))
   r_generator = padovan_r()
   l_generator = padovan_l(start='A', rules=dict(A='B', B='C', C='AB'))
   if all(len(next(l_generator)) == padovan_f(n) == next(r_generator)
          for n in range(32)):
       print("\nThe L-system, recurrence and floor based algorithms match to n=31 .")
   else:
       print("\nThe L-system, recurrence and floor based algorithms DIFFER!")</lang>
Output:
The first twenty terms of the sequence.
1, 1, 1, 2, 2, 3, 4, 5, 7, 9, 12, 16, 21, 28, 37, 49, 65, 86, 114, 151

The recurrence and floor based algorithms match to n=63 .

The first 10 L-system string-lengths and strings
    1 'A'
    1 'B'
    1 'C'
    2 'AB'
    2 'BC'
    3 'CAB'
    4 'ABBC'
    5 'BCCAB'
    7 'CABABBC'
    9 'ABBCBCCAB'

The L-system, recurrence and floor based algorithms match to n=31 .

Python: Expressed in terms of a generic anamorphism (unfoldr)

<lang python>Padovan series

from itertools import chain, islice from math import floor from operator import eq


  1. padovans :: [Int]

def padovans():

   Non-finite series of Padovan numbers,
      defined in terms of recurrence relations.
   
   def recurrence(abc):
       a, b, c = abc
       return a, (b, c, a + b)
   return unfoldr(recurrence)(
       (1, 1, 1)
   )


  1. padovanFloor :: [Int]

def padovanFloor():

   The Padovan series, defined in terms
      of a floor function.
   
   p = 1.324717957244746025960908854
   s = 1.0453567932525329623
   def f(n):
       return floor(p ** (n - 1) / s + 0.5), 1 + n
   return unfoldr(f)(0)


  1. padovanLSystem : [Int]

def padovanLSystem():

   An L-system generating terms whose lengths
      are the values of the Padovan integer series.
   
   def rule(c):
       return 'B' if 'A' == c else (
           'C' if 'B' == c else 'AB'
       )
   def f(s):
       return s, .join(list(concatMap(rule)(s)))
   return unfoldr(f)('A')


  1. ------------------------- TEST -------------------------
  1. prefixesMatch :: [a] -> [a] -> Bool

def prefixesMatch(xs, ys, n):

   True if the first n items of each
      series are the same.
   
   return all(map(eq, take(n)(xs), ys))


  1. main :: IO ()

def main():

   Test three Padovan functions for
      equivalence and expected results.
   
   print('\n'.join([
       "First 20 padovans:\n",
       repr(take(20)(padovans())),
       "\nThe recurrence and floor-based functions" + (
           " match over 64 terms:\n"
       ),
       repr(prefixesMatch(
           padovans(),
           padovanFloor(),
           64
       )),
       "\nFirst 10 L-System strings:\n",
       repr(take(10)(padovanLSystem())),
       "\nThe lengths of the first 32 L-System strings",
       "match the Padovan sequence:\n",
       repr(prefixesMatch(
           padovans(),
           (len(x) for x in padovanLSystem()),
           32
       ))
   ]))


  1. ----------------------- GENERIC ------------------------
  1. concatMap :: (a -> [b]) -> [a] -> [b]

def concatMap(f):

   A concatenated map
   def go(xs):
       return chain.from_iterable(map(f, xs))
   return go


  1. unfoldr :: (b -> Maybe (a, b)) -> b -> [a]

def unfoldr(f):

   A lazy (generator) list unfolded from a seed value
      by repeated application of f until no residue remains.
      Dual to fold/reduce.
      f returns either None, or just (value, residue).
      For a strict output list, wrap the result with list()
   
   def go(x):
       valueResidue = f(x)
       while None is not valueResidue:
           yield valueResidue[0]
           valueResidue = f(valueResidue[1])
   return go


  1. take :: Int -> [a] -> [a]
  2. take :: Int -> String -> String

def take(n):

   The prefix of xs of length n,
      or xs itself if n > length xs.
   
   def go(xs):
       return (
           xs[0:n]
           if isinstance(xs, (list, tuple))
           else list(islice(xs, n))
       )
   return go


  1. MAIN ---

if __name__ == '__main__':

   main()</lang>
Output:
First 20 padovans:

[1, 1, 1, 2, 2, 3, 4, 5, 7, 9, 12, 16, 21, 28, 37, 49, 65, 86, 114, 151]

The recurrence and floor-based functions match over 64 terms:

True

First 10 L-System strings:

['A', 'B', 'C', 'AB', 'BC', 'CAB', 'ABBC', 'BCCAB', 'CABABBC', 'ABBCBCCAB']

The lengths of the first 32 L-System strings
match the Padovan sequence:

True

Quackery

v** is defined at Exponentiation operator#Quackery.

<lang Quackery>( --------------------- Recurrence -------------------- )

 [ dup 0 = iff
    [ drop ' [ ] ] done
   dup 1 = iff
     [ drop ' [ 1 ] ] done
  dip [ [] 0 1 1 ]
  2 - times 
      [ dip [ 2dup + ] swap 
        3 pack dip join 
        unpack ]
    3 times join behead drop ] is padovan1 ( n --> [   )

 say "With recurrence:     " 20 padovan1 echo cr cr


( ------------------- Floor Function ------------------ )

 $ "bigrat.qky" loadfile

 [ [ $ "1.324717957244746025960908854"
     $->v drop join ] constant 
   do ]                        is p        (   --> n/d )

 [ [ $ "1.0453567932525329623"
     $->v drop join ] constant 
   do ]                        is s        (   --> n/d )

 [ 1 -
   p rot v** s v/ 1 2 v+ / ]   is padovan2 ( n --> n   )

 say "With floor function: "
 []
 20 times [ i^ padovan2 join ]
 echo cr cr


( ---------------------- L-System --------------------- )

 [ $ "" swap witheach 
     [ nested quackery join ] ]    is expand ( $ --> $ )

 [ $ "B" ]                         is A      ( $ --> $ )

 [ $ "C" ]                         is B      ( $ --> $ )

 [ $ "AB" ]                        is C      ( $ --> $ )

 $ "A"

 say "First 10 L System strings: "
 9 times 
   [ dup echo$ sp
     expand ]
 echo$ cr cr

 [] $ "A"
 31 times
   [ dup size
     swap dip join
     expand ]
 size join
 
 32 padovan1 = iff
   [ say "The first 32 recurrence terms and L System lengths are the same." ]
 else [ say "Oh no! It's all gone pear-shaped!" ] 

</lang>

Output:
With recurrence:     [ 1 1 1 2 2 3 4 5 7 9 12 16 21 28 37 49 65 86 114 151 ]

With floor function: [ 1 1 1 2 2 3 4 5 7 9 12 16 21 28 37 49 65 86 114 151 ]

First 10 L System strings: A B C AB BC CAB ABBC BCCAB CABABBC ABBCBCCAB

The first 32 recurrence terms and L System lengths are the same.


Raku

<lang perl6>constant p = 1.32471795724474602596; constant s = 1.0453567932525329623; constant %rules = A => 'B', B => 'C', C => 'AB';

my @pad-recur = 1, 1, 1, -> $c, $b, $ { $b + $c } … *;

my @pad-floor = { floor 1/2 + p ** ($++ - 1) / s } … *;

my @pad-L-sys = 'A', { %rules{$^axiom.comb}.join } … *; my @pad-L-len = @pad-L-sys.map: *.chars;

say @pad-recur.head(20); say @pad-L-sys.head(10);

say "Recurrence == Floor to N=64" if (@pad-recur Z== @pad-floor).head(64).all; say "Recurrence == L-len to N=32" if (@pad-recur Z== @pad-L-len).head(32).all;</lang>

Output:
(1 1 1 2 2 3 4 5 7 9 12 16 21 28 37 49 65 86 114 151)
(A B C AB BC CAB ABBC BCCAB CABABBC ABBCBCCAB)
Recurrence == Floor to N=64
Recurrence == L-len to N=32

REXX

<lang rexx>/*REXX pgm computes the Padovan seq. (using 2 methods), and also computes the L─strings.*/ numeric digits 40 /*better precision for Plastic ratio. */ parse arg n nF Ln cL . /*obtain optional arguments from the CL*/ if n== | n=="," then n= 20 /*Not specified? Then use the default.*/ if nF== | nF=="," then nF= 64 /* " " " " " " */ if Ln== | Ln=="," then Ln= 10 /* " " " " " " */ if cL== | cL=="," then cL= 32 /* " " " " " " */ PR= 1.324717957244746025960908854 /*the plastic ratio (constant). */

s= 1.0453567932525329623                        /*tge  "s"  constant.                  */
   @.= .;      @.0= 1;      @.1= 1;      @.2= 1 /*initialize 3 terms of the Padovan seq*/
   !.= .;      !.0= 1;      !.1= 1;      !.2= 1 /*     "     "   "    "  "     "     " */

call req1; call req2; call req3; call req4 /*invoke the four task's requirements. */ exit 0 /*stick a fork in it, we're all done. */ /*──────────────────────────────────────────────────────────────────────────────────────*/ floor: procedure; parse arg x; t= trunc(x); return t - (x<0) * (x\=t) pF: procedure expose !. PR s; parse arg x;  !.x= floor(PR**(x-1)/s + .5); return !.x th: parse arg th; return th||word('th st nd rd',1+(th//10)*(th//100%10\==1)*(th//10<4)) /*──────────────────────────────────────────────────────────────────────────────────────*/ L_sys: procedure: arg x; q=; a.A= 'B'; a.B= 'C'; a.C= 'AB'; if x== then return 'A'

                               do k=1  for length(x);  _= substr(x, k, 1);  q= q  ||  a._
                               end   /*k*/;                           return q

/*──────────────────────────────────────────────────────────────────────────────────────*/ p: procedure expose @.; parse arg x; if @.x\==. then return @.x /*@.X defined?*/

      xm2= x - 2;    xm3= x - 3;    @.x= @.xm2 + @.xm3;   return @.x

/*──────────────────────────────────────────────────────────────────────────────────────*/ req1: say 'The first ' n " terms of the Pandovan sequence:";

      $= @.0;  do j=1  for n-1;   $= $  p(j)
               end   /*j*/
      say $;                                                          return

/*──────────────────────────────────────────────────────────────────────────────────────*/ req2: ok= 1; what= ' terms match for recurrence and floor─based functions.'

               do j=0  for nF;  if p(j)==pF(j)  then iterate
               say 'the '   th(j)   " terms don't match:"   p(j)  pF(j);   ok= 0
               end   /*j*/
      say
      if ok  then say 'all '    nF    what;                           return

/*──────────────────────────────────────────────────────────────────────────────────────*/ req3: y=; $= 'A'

               do j=1  for Ln-1;   y= L_sys(y);    $= $  L_sys(y)
               end   /*j*/
      say
      say 'L_sys:'  $;                                                return

/*──────────────────────────────────────────────────────────────────────────────────────*/ req4: y=; what=' terms match for Padovan terms and lengths of L_sys terms.'

      ok= 1;   do j=1  for cL;  y= L_sys(y);   L= length(y)
      if       L==p(j-1)  then iterate
               say 'the '    th(j)    " Padovan term doesn't match the length of the",
                                      'L_sys term:'   p(j-1)  L;           ok= 0
               end   /*j*/
      say
      if ok  then say 'all '    cL    what;                           return</lang>
output   when using the default inputs:
The first  20  terms of the Padovan sequence:
1 1 1 2 2 3 4 5 7 9 12 16 21 28 37 49 65 86 114 151

all  64  terms match for  recurrence  and  floor─based  functions.

L_sys:  A B C AB BC CAB ABBC BCCAB CABABBC ABBCBCCAB 

all  32  terms match for Padovan terms and lengths of L_sys terms.

Ruby

<lang ruby>padovan = Enumerator.new do |y|

 ar = [1, 1, 1]
 loop do
   ar << ar.first(2).sum
   y  << ar.shift
 end

end

P, S = 1.324717957244746025960908854, 1.0453567932525329623 def padovan_f(n) = (P**(n-1) / S + 0.5).floor

puts "Recurrence Padovan: #{padovan.take(20)}" puts "Floor function: #{(0...20).map{|n| padovan_f(n)}}"

n = 63 bool = (0...n).map{|n| padovan_f(n)} == padovan.take(n) puts "Recurrence and floor function are equal upto #{n}: #{bool}." puts

def l_system(axiom = "A", rules = {"A" => "B", "B" => "C", "C" => "AB"} )

 return enum_for(__method__,  axiom, rules) unless block_given? 
 loop do
   yield axiom 
   axiom = axiom.chars.map{|c| rules[c] }.join
 end

end

puts "First 10 elements of L-system: #{l_system.take(10).join(", ")} " n = 32 bool = l_system.take(n).map(&:size) == padovan.take(n) puts "Sizes of first #{n} l_system strings equal to recurrence padovan? #{bool}." </lang>

Output:
Recurrence Padovan: [1, 1, 1, 2, 2, 3, 4, 5, 7, 9, 12, 16, 21, 28, 37, 49, 65, 86, 114, 151]
Floor function:     [1, 1, 1, 2, 2, 3, 4, 5, 7, 9, 12, 16, 21, 28, 37, 49, 65, 86, 114, 151]
Recurrence and floor function are equal upto 63: true.

First 10 elements of L-system: A, B, C, AB, BC, CAB, ABBC, BCCAB, CABABBC, ABBCBCCAB 
Sizes of first 32 l_system strings equal to recurrence padovan? true.

Rust

<lang rust>fn padovan_recur() -> impl std::iter::Iterator<Item = usize> {

   let mut p = vec![1, 1, 1];
   let mut n = 0;
   std::iter::from_fn(move || {
       let pn = if n < 3 { p[n] } else { p[0] + p[1] };
       p[0] = p[1];
       p[1] = p[2];
       p[2] = pn;
       n += 1;
       Some(pn)
   })

}

fn padovan_floor() -> impl std::iter::Iterator<Item = usize> {

   const P: f64 = 1.324717957244746025960908854;
   const S: f64 = 1.0453567932525329623;
   (0..).map(|x| (P.powf((x - 1) as f64) / S + 0.5).floor() as usize)

}

fn padovan_lsystem() -> impl std::iter::Iterator<Item = String> {

   let mut str = String::from("A");
   std::iter::from_fn(move || {
       let result = str.clone();
       let mut next = String::new();
       for ch in str.chars() {
           match ch {
               'A' => next.push('B'),
               'B' => next.push('C'),
               _ => next.push_str("AB"),
           }
       }
       str = next;
       Some(result)
   })

}

fn main() {

   println!("First 20 terms of the Padovan sequence:");
   for p in padovan_recur().take(20) {
       print!("{} ", p);
   }
   println!();
   println!(
       "\nRecurrence and floor functions agree for first 64 terms? {}",
       padovan_recur().take(64).eq(padovan_floor().take(64))
   );
   println!("\nFirst 10 strings produced from the L-system:");
   for p in padovan_lsystem().take(10) {
       print!("{} ", p);
   }
   println!();
   println!(
       "\nLength of first 32 strings produced from the L-system = Padovan sequence? {}",
       padovan_lsystem()
           .map(|x| x.len())
           .take(32)
           .eq(padovan_recur().take(32))
   );

}</lang>

Output:
First 20 terms of the Padovan sequence:
1 1 1 2 2 3 4 5 7 9 12 16 21 28 37 49 65 86 114 151 

Recurrence and floor functions agree for first 64 terms? true

First 10 strings produced from the L-system:
A B C AB BC CAB ABBC BCCAB CABABBC ABBCBCCAB 

Length of first 32 strings produced from the L-system = Padovan sequence? true

Swift

<lang swift>import Foundation

class PadovanRecurrence: Sequence, IteratorProtocol {

   private var p = [1, 1, 1]
   private var n = 0
   
   func next() -> Int? {
       let pn = n < 3 ? p[n] : p[0] + p[1]
       p[0] = p[1]
       p[1] = p[2]
       p[2] = pn
       n += 1
       return pn
   }

}

class PadovanFloor: Sequence, IteratorProtocol {

   private let P = 1.324717957244746025960908854
   private let S = 1.0453567932525329623
   private var n = 0
   
   func next() -> Int? {
       let p = Int(floor(pow(P, Double(n - 1)) / S + 0.5))
       n += 1
       return p
   }

}

class PadovanLSystem: Sequence, IteratorProtocol {

   private var str = "A"
   
   func next() -> String? {
       let result = str
       var next = ""
       for ch in str {
           switch (ch) {
           case "A": next.append("B")
           case "B": next.append("C")
           default: next.append("AB")
           }
       }
       str = next
       return result
   }

}

print("First 20 terms of the Padovan sequence:") for p in PadovanRecurrence().prefix(20) {

   print("\(p)", terminator: " ")

} print()

var b = PadovanRecurrence().prefix(64)

   .elementsEqual(PadovanFloor().prefix(64))

print("\nRecurrence and floor functions agree for first 64 terms? \(b)")

print("\nFirst 10 strings produced from the L-system:"); for p in PadovanLSystem().prefix(10) {

   print(p, terminator: " ")

} print()

b = PadovanLSystem().prefix(32).map{$0.count}

   .elementsEqual(PadovanRecurrence().prefix(32))

print("\nLength of first 32 strings produced from the L-system = Padovan sequence? \(b)")</lang>

Output:
First 20 terms of the Padovan sequence:
1 1 1 2 2 3 4 5 7 9 12 16 21 28 37 49 65 86 114 151 

Recurrence and floor functions agree for first 64 terms? true

First 10 strings produced from the L-system:
A B C AB BC CAB ABBC BCCAB CABABBC ABBCBCCAB 

Length of first 32 strings produced from the L-system = Padovan sequence? true

Wren

Library: Wren-big
Library: Wren-dynamic

L-System stuff is based on the Julia implementation. <lang ecmascript>import "/big" for BigRat import "/dynamic" for Struct

var padovanRecur = Fn.new { |n|

   var p = List.filled(n, 1)
   if (n < 3) return p
   for (i in 3...n) p[i] = p[i-2] + p[i-3]
   return p

}

var padovanFloor = Fn.new { |n|

   var p = BigRat.fromDecimal("1.324717957244746025960908854")
   var s = BigRat.fromDecimal("1.0453567932525329623")
   var f = List.filled(n, 0)
   var pow = BigRat.one
   f[0] = (pow/p/s + 0.5).floor.toInt
   for (i in 1...n) {
       f[i] = (pow/s + 0.5).floor.toInt
       pow = pow * p
   }
   return f

}

var LSystem = Struct.create("LSystem", ["rules", "init", "current"])

var step = Fn.new { |lsys|

   var s = ""
   if (lsys.current == "") {
       lsys.current = lsys.init
   } else {
       for (c in lsys.current) s = s + lsys.rules[c]
       lsys.current = s
   }
   return lsys.current

}

var padovanLSys = Fn.new { |n|

   var rules = {"A": "B", "B": "C", "C": "AB"}
   var lsys = LSystem.new(rules, "A", "")
   var p = List.filled(n, null)
   for (i in 0...n) p[i] = step.call(lsys)
   return p

}

System.print("First 20 members of the Padovan sequence:") System.print(padovanRecur.call(20))

var recur = padovanRecur.call(64) var floor = padovanFloor.call(64) var areSame = (0...64).all { |i| recur[i] == floor[i] } var s = areSame ? "give" : "do not give" System.print("\nThe recurrence and floor based functions %(s) the same results for 64 terms.")

var p = padovanLSys.call(32) var lsyst = p.map { |e| e.count }.toList System.print("\nFirst 10 members of the Padovan L-System:") System.print(p.take(10).toList) System.print("\nand their lengths:") System.print(lsyst.take(10).toList)

recur = recur.take(32).toList areSame = (0...32).all { |i| recur[i] == lsyst[i] } s = areSame ? "give" : "do not give" System.print("\nThe recurrence and L-system based functions %(s) the same results for 32 terms.")</lang>

Output:
First 20 members of the Padovan sequence:
[1, 1, 1, 2, 2, 3, 4, 5, 7, 9, 12, 16, 21, 28, 37, 49, 65, 86, 114, 151]

The recurrence and floor based functions give the same results for 64 terms.

First 10 members of the Padovan L-System:
[A, B, C, AB, BC, CAB, ABBC, BCCAB, CABABBC, ABBCBCCAB]

and their lengths:
[1, 1, 1, 2, 2, 3, 4, 5, 7, 9]

The recurrence and L-system based functions give the same results for 32 terms.