“Finite Field Arithmetic.” Chapter 4: Interlude: FFACalc.

This article is part of a series of hands-on tutorials introducing FFA, or the Finite Field Arithmetic library. FFA differs from the typical "Open Sores" abomination, in that -- rather than trusting the author blindly with their lives -- prospective users are expected to read and fully understand every single line. In exactly the same manner that you would understand and pack your own parachute. The reader will assemble and test a working FFA with his own hands, and at the same time grasp the purpose of each moving part therein.

You will need:

Add the above vpatch and seal to your V-set, and press to ch4_ffacalc.kv.vpatch.

Just like before, you will end up with two directories, libffa and ffademo.
However you will also see a new one, ffacalc.

Now compile ffacalc:

cd ffacalc
gprbuild

But do not run it quite yet.


As the title of this chapter suggests, it will not introduce fundamentally new FFA material. Instead, you will meet FFACalc -- a program which makes practical use of the routines presented in Chapters 1, 2, and 3. Henceforth every Chapter in this series will build on FFACalc, rather than continuing to expand the rather-uninteresting ffademo. When we reach the final Chapter, the reader will notice that... but let's not spoil it!

For now, FFACalc is exactly what the name implies: a FFAtronic RPN calculator, capable strictly of addition, subtraction, basic bitwise ops, numeric comparison, a small number of simple stack manipulations (a la Forth), and some elementary I/O.

But first, a few small helper-function additions to libFFA.

Calculators need to accept numeric input, and it is to be processed one hexadecimal digit at a time. Therefore a nibble subtype of Word is called for:

words.ads:

   -- Word, restricted to Nibble range.
   subtype Nibble is Word range 0 .. 16#F#;

Predicate operators produce strictly WBool (see Chapter 1) outputs. FFACalc will operate strictly in FZ integers. Therefore a conversion is required:

fz_basic.ads:

   -- Set given FZ to a given truth value
   procedure WBool_To_FZ(V : in WBool; N : out FZ);

fz_basic.adb:

   -- Set given FZ to a given truth value
   procedure WBool_To_FZ(V : in WBool; N : out FZ) is
   begin
      FZ_Clear(N);
      FZ_Set_Head(N, V);
   end WBool_To_FZ;
   pragma Inline_Always(WBool_To_FZ);

Sometimes, we will need to go in the other direction, and produce a WBool from an FZ, based on the Boolean meaning of its value (i.e. whether it is a nonzero.) This will look like this:

w_pred.ads:

   -- Return 1 if N is unequal to 0; otherwise return 0.
   function W_NZeroP(N : in Word) return WBool;

w_pred.adb:

   -- Return 1 if N is unequal to 0; otherwise return 0.
   function W_NZeroP(N : in Word) return WBool is
   begin
      return 1 xor W_ZeroP(N);
   end W_NZeroP;
   pragma Inline_Always(W_NZeroP);

Now since we are introducing a program where the user is able to control the width of an instantiated FFAtron, we will need a validity predicate. FFA "bitness" is not an arbitrary positive number, but must be an integer multiple of all historical machine word sizes, and additionally a power of two (the reason for the latter restriction will become apparent in the Sub-Quadratic Multiplication Chapter.) And so:

fz_lim.ads:

package FZ_Lim is
 
   pragma Pure;
 
   FZ_Minimal_Bitness : constant Positive := 256;
 
   FZ_Validity_Rule_Doc : constant String
     := "Must be greater than or equal to 256, and a power of 2.";
 
   -- Determine if a proposed FFA Bitness is valid.
   function FZ_Valid_Bitness_P(B : in Positive) return Boolean;
 
end FZ_Lim;

fz_lim.adb:

package body FZ_Lim is
 
   -- Determine if a proposed FFA Bitness is valid.
   function FZ_Valid_Bitness_P(B : in Positive) return Boolean is
      Result   : Boolean := False;
      T        : Natural := B;
      PopCount : Natural := 0;
   begin
      -- Supposing we meet the minimal bitness:
      if B >= FZ_Minimal_Bitness then
         while T > 0 loop
            if T mod 2 = 1 then
               PopCount := PopCount + 1;
            end if;
            T := T / 2;
         end loop;
 
         -- Is B a power of 2?
         if PopCount = 1 then
            Result := True;
         end if;
      end if;
 
      return Result;
   end FZ_Valid_Bitness_P;
 
end FZ_Lim;

In a power of 2, the "popcount" (number of 1s) is necessarily 1. The mechanics of this routine should be apparent to the alert reader, nothing more will be said of it.

And that's all for LibFFA, for the time being. Now returning to FFACalc: we will shed the old ffademo's dependence on Ada's standard I/O library, in favour of a more compact approach:

os.ads:

with Interfaces;   use Interfaces;
with Interfaces.C; use Interfaces.C;
 
 
package OS is
 
   -- Receive a character from the TTY, and True if success (False if EOF)
   function Read_Char(C : out Character) return Boolean;
 
   -- Send a character to the TTY.
   procedure Write_Char(C : in Character);
 
   -- Send a Newline to the TTY.
   procedure Write_Newline;
 
   -- Exit with an error condition report.
   procedure Eggog(M : String);
 
   procedure Quit(Return_Code : Integer);
   pragma Import
     (Convention    => C,
      Entity        => Quit,
      External_Name => "exit");
 
private
 
   -- POSIX stdio:   
   EOF : constant int := -1;
 
   function GetChar return int;
   pragma Import(C, getchar);
 
   function PutChar(item: int) return int;
   pragma Import(C, putchar);
 
   -- GNATistic
   procedure To_Stderr(C : Character);
   pragma Import(Ada, To_Stderr, "__gnat_to_stderr_char");
 
   Sadness_Code : constant Integer := -1;
 
end OS;

os.adb:

package body OS is
 
   -- Receive a character from the TTY, and True if success (False if EOF)
   function Read_Char(C : out Character) return Boolean is
      i : int;
      Result : Boolean := False;
   begin
      i := GetChar;
      if i /= EOF then
         C := Character'Val(i);
         Result := True;
      end if;
      return Result;
   end Read_Char;
 
 
   -- Send a character to the TTY.
   procedure Write_Char(C : in Character) is
      R : int;
      pragma Unreferenced(R);
   begin
      R := PutChar(int(Character'Pos(C)));
   end Write_Char;
 
 
   -- Send a Newline to the TTY.
   procedure Write_Newline is
   begin
      Write_Char(Character'Val(16#A#));
   end Write_Newline;
 
 
   -- Exit with an error condition report.
   procedure Eggog(M : String) is
   begin
      for i in 1 .. M'Length loop
         To_Stderr(M(I));
      end loop;
 
      -- Emit LF
      To_Stderr(Character'Val(16#A#));
 
      -- Exit
      Quit(Sadness_Code);
   end;
 
end OS;

Now for a bit of surprise. Did you know that it is impossible to make use of the standard Ada.Command_Line functionality in a program where the

pragma Restrictions(No_Secondary_Stack);

... restriction is in force?

The reason for this becomes apparent in a careful reading of the Standard, where we find the following turd:

function Argument (Number : in Positive) return String;

Indeed, a completely unnecessary invocation of the secondary stack ! Why did the authors of the Standard do this ? I have no idea, but we will have to correct their mistake! Unfortunately it is quite impossible to do this without invoking some GNATisms. And so, we must:

cmdline.ads:

with System;
 
package CmdLine is
 
   -- IMHO this is reasonable.
   CmdLineArg_Length : constant Positive := 256;
 
   subtype CmdLineArg is String(1 .. CmdLineArg_Length);
 
   function Initialized return Boolean;
 
   function Arg_Count return Natural;
   pragma Import(C, Arg_Count, "__gnat_arg_count");
 
   procedure Get_Argument(Number : in  Natural;
                          Result : out String);
 
private
 
   procedure Fill_Arg (A : System.Address; Arg_Num : Integer);
   pragma Import(C, Fill_Arg, "__gnat_fill_arg");
 
   function Len_Arg (Arg_Num : Integer) return Integer;
   pragma Import(C, Len_Arg, "__gnat_len_arg");
 
end CmdLine;

cmdline.adb:

with System; use System;
 
package body CmdLine is
 
   -- Test if GNAT's cmdline mechanism is available
   function Initialized return Boolean is
      gnat_argv : System.Address;
      pragma Import (C, gnat_argv, "gnat_argv");
 
   begin
      return gnat_argv /= System.Null_Address;
   end Initialized;
 
 
   -- Fill the provided string with the text of Number-th cmdline arg
   procedure Get_Argument(Number : in  Natural;
                          Result : out String) is
   begin
      if Number >= Arg_Count or (not Initialized) then
         raise Constraint_Error;
      end if;
 
      declare
         L   : constant Integer := Len_Arg(Number);
         Arg : aliased String(1 .. L);
      begin
         -- Will it fit into the available space?
         if L > Result'Length then
            raise Constraint_Error;
         end if;
 
         -- Get this arg string from where GNAT stowed it
         Fill_Arg(Arg'Address, Number);
 
         -- Copy it to Result:
         Result := (others => ' ');
         Result(Arg'Range) := Arg;
      end;
   end Get_Argument;
 
end CmdLine;

How this is invoked, will soon become quite apparent. Let's at last proceed to FFACalc !

We make use here of nearly everything we have seen in Chapters 1-3:

ffa_calc.adb:

-- Basics
with OS;          use OS;
with CmdLine;     use CmdLine;
 
-- FFA
with FZ_Lim;   use FZ_Lim;
with Words;    use Words;
with W_Pred;   use W_Pred;
with FZ_Type;  use FZ_Type;
with FZ_Basic; use FZ_Basic;
with FZ_Arith; use FZ_Arith;
with FZ_Cmp;   use FZ_Cmp;
with FZ_Pred;  use FZ_Pred;
with FZ_BitOp; use FZ_BitOp;
with FZ_Shift; use FZ_Shift;
 
-- For Output
with FFA_IO;   use FFA_IO;
procedure FFA_Calc is
 
   Width  : Positive; -- Desired FFA Width
   Height : Positive; -- Desired Height of Stack
 
begin
   if Arg_Count /= 3 then
      Eggog("Usage: ./ffa_calc WIDTH HEIGHT");
   end if;
 
   declare
      Arg1 : CmdLineArg;
      Arg2 : CmdLineArg;
   begin
      -- Get commandline args:
      Get_Argument(1, Arg1); -- First arg
      Get_Argument(2, Arg2); -- Second arg
 
      -- Parse into Positives:
      Width  := Positive'Value(Arg1);
      Height := Positive'Value(Arg2);
   exception
      when others =>
         Eggog("Invalid arguments!");
   end;
 
   -- Test if proposed Width is permissible:
   if not FZ_Valid_Bitness_P(Width) then
      Eggog("Invalid Width: " & FZ_Validity_Rule_Doc);
   end if;

Above, we see how our replacement for Ada's standard command-line argument reader works. Instead of demanding the secondary stack, we make use of pre-allocated strings, into which each argument is copied. The reader is invited to try and overflow these: the resulting death is a clean one.

Now for the calculator...

   -- The Calculator itself:
   declare
 
      -- The number of Words required to make a FZ of the given Bitness.
      Wordness : Indices := Indices(Width / Bitness);
 
      --------------------------------------------------------
      -- State --
      --------------------------------------------------------
      -- The Stack:
      subtype Stack_Positions is Natural range 0 .. Height;
      type Stacks is array(Stack_Positions range <>) of FZ(1 .. Wordness);
      Stack      : Stacks(Stack_Positions'Range);
 
      -- Stack Pointer:
      SP         : Stack_Positions := Stack_Positions'First;
 
      -- Carry/Borrow Flag:
      Flag       : WBool   := 0;
 
      -- Odometer:
      Pos        : Natural := 0;
 
      -- The current levels of the three types of nestedness:
      QuoteLevel : Natural := 0;
      CommLevel  : Natural := 0;
      CondLevel  : Natural := 0;
      --------------------------------------------------------

Observe that the FORTH-like stack is allocated on the stack (your machine's, that is), and its height is determined by the HEIGHT parameter given in the second command line argument. The width of the FZ integers comprising the elements of this stack, is in turn given by WIDTH, the first command line argument.

Now for some elementary stack-manipulation routines:

      -- Clear the stack and set SP to bottom.
      procedure Zap is
      begin
         -- Clear the stack
         for i in Stack'Range loop
            FZ_Clear(Stack(i));
         end loop;
         -- Set SP to bottom
         SP   := Stack_Positions'First;
         -- Clear Overflow flag
         Flag := 0;
      end Zap;
 
 
      -- Report a fatal error condition at the current symbol
      procedure E(S : in String) is
      begin
         Eggog("Pos:" & Natural'Image(Pos) & ": " & S);
      end E;
 
 
      -- Move SP up
      procedure Push is
      begin
         if SP = Stack_Positions'Last then
            E("Stack Overflow!");
         else
            SP := SP + 1;
         end if;
      end Push;
 
 
      -- Discard the top of the stack
      procedure Drop is
      begin
         FZ_Clear(Stack(SP));
         SP := SP - 1;
      end Drop;
 
 
      -- Check if stack has the necessary N items
      procedure Want(N : in Positive) is
      begin
         if SP < N then
            E("Stack Underflow!");
         end if;
      end Want;

Here we make use of the FZ_ShiftLeft operation we implemented in Chapter 3:

      -- Slide a new hex digit into the FZ on top of stack
      procedure Ins_Hex_Digit(N : in out FZ;
                              D : in Nibble) is
         Overflow : Word := 0;
      begin
         -- Make room in this FZ for one additional hex digit
         FZ_ShiftLeft_O(N        => N,
                        ShiftedN => N,
                        Count    => 4,
                        Overflow => Overflow);
 
         -- Constants which exceed the Width are forbidden:
         if W_NZeroP(Overflow) = 1 then
            E("Constant Exceeds Bitness!");
         end if;
 
         -- Set the new digit
         FZ_Or_W(N, D);
      end;

And now for the "opcodes" comprising our stack machine:

      -- Execute a Normal Op
      procedure Op_Normal(C : in Character) is
 
         -- Over/underflow output from certain ops
         F : Word;
 
      begin
 
         case C is
 
            --------------
            -- Stickies --
            --------------
            -- Enter Commented
            when '(' =>
               CommLevel := 1;
 
               -- Exit Commented (but we aren't in it!)
            when ')' =>
               E("Mismatched close-comment parenthesis !");
 
               -- Enter Quoted
            when '[' =>
               QuoteLevel := 1;
 
               -- Exit Quoted (but we aren't in it!)
            when ']' =>
               E("Mismatched close-quote bracket !");
 
               -- Enter a ~taken~ Conditional branch:
            when '{' =>
               Want(1);
               if FZ_ZeroP(Stack(SP)) = 1 then
                  CondLevel := 1;
               end if;
               Drop;
 
               -- Exit from a ~non-taken~ Conditional branch:
               -- ... we push a 0, to suppress the 'else' clause
            when '}' =>
               Push;
               WBool_To_FZ(0, Stack(SP));
 
               ----------------
               -- Immediates --
               ----------------
 
               -- These operate on the FZ ~currently~ at top of the stack;
               -- and this means that the stack may NOT be empty.
 
            when '0' .. '9' =>
               Want(1);
               Ins_Hex_Digit(Stack(SP),
                             Character'Pos(C) - Character'Pos('0'));
 
            when 'A' .. 'F' =>
               Want(1);
               Ins_Hex_Digit(Stack(SP),
                             10 + Character'Pos(C) - Character'Pos('A'));
 
            when 'a' .. 'f' =>
               Want(1);
               Ins_Hex_Digit(Stack(SP),
                             10 + Character'Pos(C) - Character'Pos('a'));
 
               ------------------
               -- Stack Motion --
               ------------------
 
               -- Push a 0 onto the stack
            when '.' =>
               Push;
               FZ_Clear(Stack(SP));
 
               -- Dup
            when '″' =>
               Want(1);
               Push;
               Stack(SP) := Stack(SP - 1);
 
               -- Drop
            when '_' =>
               Want(1);
               Drop;
 
               -- Swap
            when ''' =>
               Want(2);
               FZ_Swap(Stack(SP), Stack(SP - 1));
 
               -- Over
            when '`' =>
               Want(2);
               Push;
               Stack(SP) := Stack(SP - 2);
 
               ----------------
               -- Predicates --
               ----------------
 
               -- Equality
            when '=' =>
               Want(2);
               WBool_To_FZ(FZ_Eqp(X => Stack(SP),
                                  Y => Stack(SP - 1)),
                           Stack(SP - 1));
               Drop;
 
               -- Less-Than
            when '< ' =>
               Want(2);
               WBool_To_FZ(FZ_LessThanP(X => Stack(SP - 1),
                                        Y => Stack(SP)),
                           Stack(SP - 1));
               Drop;
 
               -- Greater-Than
            when '>' =>
               Want(2);
               WBool_To_FZ(FZ_GreaterThanP(X => Stack(SP - 1),
                                           Y => Stack(SP)),
                           Stack(SP - 1));
               Drop;
 
               ----------------
               -- Arithmetic --
               ----------------
 
               -- Subtract
            when '-' =>
               Want(2);
               FZ_Sub(X          => Stack(SP - 1),
                      Y          => Stack(SP),
                      Difference => Stack(SP - 1),
                      Underflow  => F);
               Flag := W_NZeroP(F);
               Drop;
 
               -- Add
            when '+' =>
               Want(2);
               FZ_Add(X        => Stack(SP - 1),
                      Y        => Stack(SP),
                      Sum      => Stack(SP - 1),
                      Overflow => F);
               Flag := W_NZeroP(F);
               Drop;
 
               -----------------
               -- Bitwise Ops --
               -----------------
 
               -- Bitwise-And
            when '&' =>
               Want(2);
               FZ_And(X      => Stack(SP - 1),
                      Y      => Stack(SP),
                      Result => Stack(SP - 1));
               Drop;
 
               -- Bitwise-Or
            when '|' =>
               Want(2);
               FZ_Or(X      => Stack(SP - 1),
                     Y      => Stack(SP),
                     Result => Stack(SP - 1));
               Drop;
 
               -- Bitwise-Xor
            when '^' =>
               Want(2);
               FZ_Xor(X      => Stack(SP - 1),
                      Y      => Stack(SP),
                      Result => Stack(SP - 1));
               Drop;
 
               -- Bitwise-Not (1s-Complement)
            when '~' =>
               Want(1);
               FZ_Not(Stack(SP), Stack(SP));
 
               -----------
               -- Other --
               -----------
 
               -- mUx
            when 'U' =>
               Want(3);
               FZ_Mux(X      => Stack(SP - 2),
                      Y      => Stack(SP - 1),
                      Result => Stack(SP - 2),
                      Sel    => FZ_NZeroP(Stack(SP)));
               Drop;
               Drop;
 
               -- Put the Overflow flag on the stack
            when 'O' =>
               Push;
               WBool_To_FZ(Flag, Stack(SP));
 
               -- Print the FZ on the top of the stack
            when '#' =>
               Want(1);
               Dump(Stack(SP));
               Drop;
 
               -- Zap (reset)
            when 'Z' =>
               Zap;
 
               -- Quit with Stack Trace
            when 'Q' =>
               for I in reverse Stack'First + 1 .. SP loop
                  Dump(Stack(I));
               end loop;
               Quit(0);
 
               ----------
               -- NOPs --
               ----------
 
               -- Ops we have not yet spoken of -- do nothing
            when others =>
               null;
 
         end case;
 
      end Op_Normal;
 
 
      -- Process a Symbol
      procedure Op(C : in Character) is
      begin
         -- First, see whether we are in a state of nestedness:
 
         -- ... in a Comment block:
         if CommLevel > 0 then
            case C is
               when ')' =>  -- Drop a nesting level:
                  CommLevel := CommLevel - 1;
               when '(' =>  -- Add a nesting level:
                  CommLevel := CommLevel + 1;
               when others =>
                  null; -- Other symbols have no effect at all
            end case;
 
            -- ... in a Quote block:
         elsif QuoteLevel > 0 then
            case C is
               when ']' =>   -- Drop a nesting level:
                  QuoteLevel := QuoteLevel - 1;
               when '[' =>   -- Add a nesting level:
                  QuoteLevel := QuoteLevel + 1;
               when others =>
                  null; -- Other symbols have no effect on the level
            end case;
 
            -- If we aren't the mode-exiting ']', print current symbol:
            if QuoteLevel > 0 then
               Write_Char(C);
            end if;
 
            --- ... in a ~taken~ Conditional branch:
         elsif CondLevel > 0 then
            case C is
               when '}' =>   -- Drop a nesting level:
                  CondLevel := CondLevel - 1;
 
                  -- If we exited the Conditional as a result,
                  -- we push a 1 to trigger the possible 'else' clause:
                  if CondLevel = 0 then
                     Push;
                     WBool_To_FZ(1, Stack(SP));
                  end if;
 
               when '{' =>   -- Add a nesting level:
                  CondLevel := CondLevel + 1;
               when others =>
                  null; -- Other symbols have no effect on the level
            end case;
         else
            -- This is a Normal Op, so proceed with the normal rules.
            Op_Normal(C);
         end if;
 
      end Op;
 
 
      -- Current Character
      C : Character;
 
   begin
      -- Reset the Calculator      
      Zap;
      -- Process characters until EOF:
      loop
         if Read_Char(C) then
            -- Execute Op:
            Op(C);
            -- Advance Odometer
            Pos := Pos + 1;
         else
            Zap;
            Quit(0); -- if EOF, we're done
         end if;
      end loop;
   end;
 
end FFA_Calc;

But rather than describing in detail the operation of FFACalc, I will invite the reader to build it, and solve the following puzzle:


Write a FFACalc tape that will take seven numbers, presumed to be on the top of the stack, and return the largest.

Your answer should work with any legal WIDTH, and any stack HEIGHT large enough to hold the working set.

For instance, suppose file numbers.txt were to contain:

.9.1.7.5.1.1.0

Then the following example invocation:

cd ffacalc
gprbuild
cat numbers.txt youranswer.txt |  ./bin/ffa_calc 256 16

... should produce the output:

0000000000000000000000000000000000000000000000000000000000000009

... and similarly for any other seven numbers.

A solution will be posted in the next Chapter.


~To be continued!~

This entry was written by Stanislav , posted on Saturday December 23 2017 , filed under Ada, Bitcoin, Cold Air, Computation, Cryptography, FFA, Friends, Mathematics, NonLoper, ShouldersGiants, SoftwareSucks . Bookmark the permalink . Post a comment below or leave a trackback: Trackback URL.

24 Responses to ““Finite Field Arithmetic.” Chapter 4: Interlude: FFACalc.”

  • apeloyee says:

    That's splitting hairs, but
    if T mod 2 = 1 then
    PopCount := PopCount + 1;
    end if;

    could be
    PopCount := PopCount + T mod 2;

    or even just check that (T and (T - 1)) = 0 (might be too clever, and needs type conversion)

    And why Ins_Hex_Digit doesn't use FZ_ShiftLeft_O_I ? Seems tailor-made for that.

    • Stanislav says:

      Dear apeloyee,

      Re: popcount: good point, and I'll put this in.

      Re: the digits: using FZ_ShiftLeft_O_I would require first shifting the nibble so that it sits at the top of a word, which imho is ugly.

      Yours,
      -S

  • phf says:

    first posted elsewhere, the sha1 of my solution to the puzzle is b579b2c553ee2bd3aee8d17d96ae259abfad2ac5

    i'll post the complete solution here, once next chapter is released!

  • apeloyee says:

    subtype Stack_Positions is Natural range 0 .. Height;
    type Stacks is array(Stack_Positions range ) of FZ(1 .. Wordness);
    Stack : Stacks(Stack_Positions'Range);

    This is somewhat tricky. From the rest of the code, the Stack(0) is never used. Why not declare it as Stack : Stacks(Stack_Positions'First +1 .. Stack_Positions'Last );
    or preferably simply Stack : Stacks(1 .. Height ); (given as |Want| already assumes indices start from 1, rather than using Stack'First)?

    • Stanislav says:

      Dear apeloyee,

      This won't work, think about why:

      Stack(SP) must be a valid reference at all times, even when the stack is empty, or the program will barf at elaboration.

      We're stuck with the 'wasted' FZ at the bottom of the stack.

      Yours,
      -S

      • apeloyee says:

        Can you cite the clause of the Adastandard requiring that?
        It does seem to build and work with this change. (Of course, the code for the 'Q' command needs to be changed also).

        • Stanislav says:

          Dear Apeloyee,

          My observation came from my original experiments, where instead of the ugly repeating Stack(SP - 1), etc. references I had a "rename" clause at the head of the proggy; this croaked, as Stack(SP - 1), - 2, etc are invalid when SP is already at rock-bottom, even if the "rename" var is not referenced at any time afterwards in the scope.

          I have not yet found where in the Standard this behaviour is specified.

          Please consider posting your version of the routine ? If it works, and I can justify that it always must work (rather than accidentally) -- I will put it into use and cite you in the commentary.

          Yours,
          -S

          • apeloyee says:

            > I had a “rename” clause at the head of the proggy; this croaked, as Stack(SP – 1), – 2, etc are invalid when SP is already at rock-bottom, even if the “rename” var is not referenced at any time afterwards in the scope.

            I didn't know such a version existed. Not surprising, then.

            > Please consider posting your version of the routine ? If it works, and I can justify that it always must work (rather than accidentally) — I will put it into use and cite you in the commentary.

            http://p.bvulpes.com/pastes/BDpG6/?raw=true

            Corresponds to present ch. 6, with two differences mentioned. In any case, Stack(0) never needs to be accessed, and if forbidding this access doesn't work, it means original version has a bug.

            • apeloyee says:

              For the time when the paste vanishes:
              @@ -82,7 +82,7 @@
              -- The Stack:
              subtype Stack_Positions is Natural range 0 .. Height;
              type Stacks is array(Stack_Positions range ) of FZ(1 .. Wordness);
              - Stack : Stacks(Stack_Positions'Range);
              + Stack : Stacks(1..Height);

              -- Stack Pointer:
              SP : Stack_Positions := Stack_Positions'First;
              @@ -449,7 +449,7 @@

              -- Quit with Stack Trace
              when 'Q' =>
              - for I in reverse Stack'First + 1 .. SP loop
              + for I in reverse Stack'First .. SP loop
              Dump(Stack(I));
              end loop;
              Quit(0);

  • PeterL says:

    I managed to find an answer to the puzzle, at first it seemed very hard to figure out what each of the commands do, but then suddenly it clicked in my brain and it all makes sense. The sha1 of my solution is fcdd13ea71f291ffbf59ce34831b0f99173a9e5e , phf beat me to an answer by a few days, I wonder if we solved it the same way? This was fun.

    Anyway, my sig for the patch, ffa_ch4_ffacalc.vpatch.peterl.sig

    -----BEGIN PGP SIGNATURE-----
    Version: GnuPG v1

    iQIcBAABAgAGBQJaQxNbAAoJELTi4Nystj0lRFYP/3BzzsKZDSNXIqvl45TjP0rK
    z8COLZgL9jwV6dHyRY9RqmBkGVpW3XQbfDwvfI4JtOeJ0kZOOt2eixuFthE23jrg
    V9bsLInjaT6cDvUh4xc3zkHxPan5xGfRb2riUysMrCp9lQysU7qyIEGqVEwhxBUV
    JKwC6AnCHmaW5bmeCwVQmGg0ujFh4KmhYzztDxYnliiWlm7fqCYYzrnCB43MUdeU
    kcIbGxhZaN9PAM6JqWDLlybvewktyCfTACxSZbmamcE/XHk8VV28ziKzNZ72cqVZ
    YVbrgIoDXmqNwdlVUpUufnHyVdFkF8nSZ0folzj7llMjoeYOzJQJuxUuELSz8883
    5tRGTq3CT5w5JdDEJGjJYMjQXRGfVt0fZawRuZWCOl+JePl9fkVtRfwgayTco0Y7
    NQ4DftzndItMwze1ZAeA3afSl1uUM7nysc7M6jGtxkYSFnLXAS+dQyGz58lvsjDW
    0epzfH3ssPNZ9328h3QQ93tDPQFGSlKDrYP4eqngLj8bBjh9cliLicHUy8jqHzO6
    uP2LgnjAoBWC3IdAie4OBxzYSOZViY/EzIRk78jSaEuEIVDkT8jCEnzNlK0n0JVA
    xKTWE/fYvcxB5pVGde1FJLGT1HHau8EUSuz92K+lfEcZqHPGrtOWNekJUkJUYSFL
    Fzl9e5jWJ8gM3TGZlsDQ
    =Xta0
    -----END PGP SIGNATURE-----

  • Diana Coman says:

    Tiny nitpick: while I enjoy on a level "Nibble" as type name, wouldn't this be more accurately named Hex_Digit or similar? Especially since it is anyway used as such in Ins_Hex_Digit so it is rather fixed as hex, isn't it?

    • Stanislav says:

      Dear Diana Coman,

      Funnily enough I originally had it named "Hex_Digit", and renamed to "Nibble" on account of the latter being the customary name for a quantity of bitness 4.

      Yours,
      -S

  • -----BEGIN PGP SIGNATURE-----

    iQIcBAABCgAGBQJaUBQjAAoJEPAbzAMu8lJHBxsP/3OfFNzdpNx3ZKJCKBuealxM
    fBS+8l9/mJM8hslygYBZZ5BqX3Cpoi5FoQP6OKwaesB8x3jibmBcC0aK3qS0J0aG
    c1R7R09Xz0s5sx+5lvILFeDfYP68eeGKksYztT7DbOp3IfKwEV1W4eqsKqCo+LOa
    iPpVc3hD9dl1UYVThJDWRoZgSd8dUe9gj64zoEdN8VMDYal78mrCgQoR5ksj41c1
    PpiAJ1LlcVumdIyOzs8W3e1BzTn1wtOXFZIiFDPEgOJUBQ/fuYabffToMEn49tcO
    6P5Uc8JuywHShOeAYdlnN5Qb/6uiWrSpc0nIIdYH9hVT5E6ilBWQP+hZwW3Z9KuA
    2wbYp/BzbZpP0/fJ+nJShReds2xYK3zjmKgsUeWSpJP4JGZCM/qBXKhO7vBxouGT
    io0DLLbi+OmEyhkFSAEyn0z4VoytplTRg/gq+0BhICWdQ1IbkRZOuS+tapzKvP2/
    DO9qSWzL6WHoMJQh6wHLVNM5Hxp/Ri7WzbgRHd8Qr08VS/htk1TmHpSZqoUb0qKt
    aq5/ZlIWqxlIKGuTpk5+Jt7XYzUVf/8nKkWyZHmlIF/IXa1MBAEBq1JKwQwfI0bu
    IKe+zb1eMNJNhH+19qvwDx6hM5bCNfaic9LeMn2UaxnhuRUzy6udKkZTmb9AAuOC
    adpnTDp9VKqUSgTsiYG1
    =1N4B
    -----END PGP SIGNATURE-----

  • spyked says:

    Dear Stan,

    I had a lot of fun getting acquainted with FFACalc! I've posted a solution to the puzzle (along with some doodling on FFA) on my blog. Also, following Diana's example, I've posted the seals to chapters 2-4 on a separate page.

  • Diana Coman says:

    Another nitpick, at http://btcbase.org/patches/ffa_ch4_ffacalc.kv#L85 : shouldn't Result actually be of type CmdLineArg? As it is now, its range might even be different from 1.. so checking the length is not even enough. At any rate, I searched and did notice that Get_Argument is indeed always called with a CmdLineArg var, as it makes sense.

  • shinohai says:

    Signature for Chapter 4:
    -----BEGIN PGP SIGNATURE-----

    iQIzBAABCgAdFiEEJg+le85nelwEv2C6SnWIPMGx00wFAl4Is7UACgkQSnWIPMGx
    00zfWA//WSFRGTrVRkES/vZphYs+69nx8iHe08LgzS0Uk6PcQa8j8vKlaydgTXJC
    A+1cOvueqlVNUlSRjMqK+r2ZihUtDdaHSFrfZ4Abngf5bHfqMeNw7TT/8lcH/Yzd
    xUaaUD02r/D5UpBeohcQvyQnIhlDCu49KHPHKqa1sbGDrkjgPP+7fh3MphgPk2UQ
    r6q8AjHSZdgsquvVLqqHouOEv4XWkzuoy2v4RGKZWTJd8yiIIgY0CTa1BhZ9p9HC
    ij+p+icfbDUQNtoVuiwMXrz+kvyqs145p8EKM4JH0buBquw6r4VWoPIPe0L/TO7I
    dTkw0wt09MexUcIbzYI6TmUFgufZylKWF3bVwwFsV1oK3Sb5UbKD/GVxtPlX6nrE
    GJPt3zwViZ3TWR4qhljpM6X0NLy6axkCDc7InDgDQowAFY9PeMDy3htntGiP2qSG
    +AjL7WpYqRK+EzyKlRACToRG8EQcODTtIC4/O0xdRmoR73y/Sbn8d6Gli2chwtkR
    gpNY1jmCH/gJXD6o+QFIMSIb+4cvPZY3n+Tf9fXOVMlD8DFI4C4hsJnxbif6suLR
    8WNOdms9B/SswXhK6lemIaTN6ASRlx+dwJW59sTfP5tnQrWJxOD8Hrr8dGU5gB/x
    dPatHlICsZ5BW92dm8OnGvmungpRF8eMjoTGoj3AEMeqm6JwAmQ=
    =32Qc
    -----END PGP SIGNATURE-----

    Per usual, mirror of patches/seals lives @ http://btc.info.gf/devel/ada/ffa/

  • jonsykkel says:

    W_NZeroP pasted here is supposed to be FZ_NZeroP (check fz_pred.adb in the code)

Leave a Reply

XHTML: You can use these tags: <a href="" title=""> <abbr title=""> <acronym title=""> <b> <blockquote cite=""> <cite> <code> <del datetime=""> <em> <i> <q cite=""> <s> <strike> <strong> <pre lang="" line="" escaped="" highlight="">


MANDATORY: Please prove that you are human:

54 xor 84 = ?

What is the serial baud rate of the FG device ?


Answer the riddle correctly before clicking "Submit", or comment will NOT appear! Not in moderation queue, NOWHERE!