{*
 * CODEBOX.PAS
 *
 * written by : Stephen J. Friedl
 *              Software Consultant
 *
 *  This is the Codebox unit that lets us talk to the printer in very high
 *  level terms. Basically, we can set some parameters and then cause them
 *  to be set in a big loop.
 *
 *  The main entry points to this module are the "DoXxxxx" methods, which
 *  cause a certain set of send/response transactions to be started. This
 *  is fairly intricate stuff, and we try to make this as robust as possible.
 *  Unfortunately this makes it more confusing.
 *
 *  When we call a "DoXxxx" method, it suggests a sequence of send/response
 *  transactions, and we have to wait for each response. Because we are
 *  determined to be entire non-blocking, this means we require an elaborate
 *  state machine to minimize the code for each state.
 *
 *  When we call DoXxxx, we pass the address of a callback procedure. At each
 *  step in the process this procedure is called with an argument that tells
 *  the calling function what stage we are at in the state machine. Valid
 *  states are "startup", "intermediate step", "success" and "failure". Except
 *  for the "succes" and "failure" steps, these callbacks are for info
 *  purposes only (presumably status reporting or other user feedback).
 *
 *  Internally we have structured these states to be robust and minimal.
 *  Each send/resposne transaction actually has two states: the part that
 *  sends the packet to the Codebox and the part that matches the response.
 *  The sending part is fairly straightforward, but the matching part is
 *  the one where the robustness comes in.  At each match, we see if the
 *  packet we received is what was expected. If not, we basically drop the
 *  packet and wait some more. Eventually we will get a timeout, at which
 *  point we send the packet again. After a certain number of these we
 *  simply bail on the entire transaction.
 *
 *  GUARANTEEING COMPLETION
 *  -----------------------
 *  When the caller starts up one of these initializations, we *must* insure
 *  that we somehow promise that we'll finish. In most cases, it all works
 *  OK so we have normal completion. Each of the send/responses has a timeout
 *  also, and we get control when one of these happens also. However, it is
 *  possible that we could receive some random transmission from the Codebox
 *  (a status report, a print ack, whatever) that stops the timer, so we
 *  have to be careful to continually be sure that a timer is always running.
 *
 *  However, we really should set some kind of overall timer that is much
 *  longer (say, 10 seconds or something) that guarantees that we eventually
 *  regain control.
 *
 * SERIOUS POSSIBLE ERRORS
 * -----------------------
 * There are two kinds of programming problems we can get into here. First is
 * the endless loop where we keep running through the while loop and never
 * exiting (say, if we forget to increment a state or something). To guard
 * against this, we keep a counter and fail when we've had an "unreasonable"
 * number of loops.
 *
 * The other is to enter a state that has no handler for it (i.e., the "else"
 * case).  This is always a programming bug, and we must generate a serious
 * error here.
 *
 * CHOOSING STATE IDs
 * ------------------
 * We hesitatingly use integers for the state IDs, and there are a few rules
 * associated with them.  For any given send/match transaction, the matching
 * state must always be one more than the sending state. This is so that we
 * can reliably use Inc(InitializationState) to transit from send->match and
 * use Dec(InitializationState) to request a retry upon failure.
 *
 * We suggest using units of ten, but other choices can work also.
 *}
unit Codebox;

interface

uses
    Classes, SysUtils,
    Forms,
    Debug,
    CComm,
    PComm,
    Setup,
    CBPacket;

type
    ECodeboxError = class(Exception);

    {*-----------------------------------------------------------------------
     * This is the record we use when taking a snapshot of the printer before
     * we start messing around with it. The intention is to do our thing, and
     * then "put back" these settings for use with the standard Oyster
     * terminal.
     *
     * This module doesn't do anything about the .INI file they go in or
     * displaying them, but we do have two entry points: take snapshot
     * and restore snapshot.
     *}
    TSavedCodeboxSetup = record
        setupname       : String;           { name for this setup           }
        print_go_delay  : Integer;          { delay in strokes              }
        PD_assign       : Integer;          { 0=disabled 1=std detector     }
        PD_level        : Boolean;          { print-go signal lvl high/low  }
        PD_debounce     : Integer;          { debounce time x 100 uSec      }
        Contin_enabled  : Boolean;          { continuous print enabled?     }
        Contin_pitch    : Integer;          { .. and pitch                  }
        Print_formats   : TCBPrintFormats;  { bold, reverse, etc.           }
        Messages        : array[1..24] of string;       { unused yet        }
{       Setups          : array[1..17] of TCBStatus;  } { various setups    }
        nsetups         : Integer;
    end;

    { this is a record passed from the caller to the DoJobSetup method }
    TCodeboxJob = record
        msgno       : Shortint;             { message number to use         }
        headno      : Shortint;             { which head to use             }
        msg         : String;               { message to download           }
        startser    : Integer;              { starting serial number        }
        endser      : Integer;              { ending serialno (length of job) }
        serwidth    : Shortint;             { serial number width           }
        serialized  : Boolean;              { serialized?                   }
    end;

    TCodebox = class(TCBPacket)
      public constructor Create(AOwner: TComponent); override;
      public destructor  Destroy; override;

      {----------------------------------------------------------------------
       * this section contains all the parsed information that we receive
       * from the other end. They are all maintained by the PreprocessPacket
       * method and should not be set by the user.
       *
       * ===NOTE: we don't have any way to know whether a particular variable
       * is valid just by looking at it. Instead, it is only valif if the
       * user's handler is called with the corresponding packet type or
       * after the handshake sequence passed OK. Otherwise don't look at
       * them, OK?
       *
       * Note further that many of the parse_xxx routines will update some
       * of their var parameters and not others in the face of conversion
       * errors,
       *}
      public Curr_printer_ID        : TCBPrinterID;
      public Curr_printer_config    : TCBPrinterConfig;
      public Curr_stroke_period     : LongInt;
      public Curr_realtime_clk      : TCodeboxTime;
      public Curr_print_go_delay    : Integer;      { head 1 only, sorry }
      public Curr_flight_time       : Integer;      { head 1 only, sorry }
      public Curr_PD_assign         : Integer;      { 0=disabled or 1..2 }
      public Curr_PD_level          : Boolean;      { True=high False=low }
      public Curr_PD_debounce       : Integer;      { debounce time x 100 uSec }
      public Curr_head_enable       : Boolean;      { head enabled? }
      public Curr_messages          : array[1..24] of string;
      public Curr_print_formats     : TCBPrintFormats;

      public Curr_msg_num           : Integer;
      public Curr_contin_enabled    : Boolean;
      public Curr_contin_pitch      : Integer;
      public Curr_status            : TCBStatus;

      {*--------------------------------------------------------------------------------
       * these are parameters associated with the current job.
       *}
      public CurrentJob: TCodeboxJob;

      private procedure PreprocessPacket(var pak: TRcvPacket); override;

      {*---------------------------------------------------------------------
       * We can request that the Codebox notify us whenever it finishes
       * printing a particular message, and this gives us the user hook to
       * do something with it.
       *
       * ===NOTE: this function is dispatched every time we get the print
       * ack, but we've seen that we lose them for some reason. Don't count
       * on getting *every* *single* *one*.
       *}
      private FOnPrintACK: TNotifyEvent;
      published property OnPrintACK: TNotifyEvent
                            read FOnPrintACK write FOnPrintAck;

    private function got_match(b:Boolean): Boolean;
    private procedure enter_match_state(var Finished: Boolean);
    private function matched_input(const pk: TRcvPacket; rt: TRcvType;
                                cmd: ShortInt; var Finished:Boolean): Boolean;

    {--- take snapshot of the Codebox --------------------------------------}
    public procedure DoTakeSnapshot(h: TCInitEvent; var snap: TSavedCodeboxSetup);
    private procedure TakeSnapshotHandler(Sender: TObject; var pak: TRcvPacket);
    private curr_snap: ^TSavedCodeboxSetup;

    {-- initial setup (includes old InitialInquiry handler) ----------------}
    public procedure DoInitialSetup(h: TCInitEvent);
    private procedure InitialSetupHandler(Sender: TObject; var pak: TRcvPacket);

    {-- job setup ----------------------------------------------------------}
    public procedure DoJobSetup(h: TCInitEvent; const job: TCodeboxJob);
    private procedure JobSetupHandler(Sender: TObject; var pak: TRcvPacket);

    {-- job setup ----------------------------------------------------------}
    public procedure DoRunJob(h: TCInitEvent);
    private procedure RunJobHandler(Sender: TObject; var pak: TRcvPacket);

    end;

implementation

constructor TCodebox.Create(AOwner: TComponent);
begin
    inherited Create(AOwner);

    Curr_Printer_ID  := TCBPrinterId.Create;

end;

destructor TCodebox.Destroy;
begin
    Curr_Printer_ID.Destroy;

    inherited Destroy
end;

{*---------------------------------------------------------------------------
 * this inherited method lets us parse each packet as it arrives and puts it
 * in a predictible place inside our own Codebox structure, and we can turn
 * a bad command packet into a junk one so the retry/timeout mechanism works
 * nicely with it. Currently we retry on a NAK or a timeout and adding "packet
 * failed parse" makes it entirely robust.
 *
 * This routine is permitted to alter the packet provided to it.
 *
 * ===TODO: not sure whether we should inherit the current code first or last.
 * Currently all it does is report to the user that a packet arrived, but
 * it's not clear whether we should give them the before or after.  For now
 * we'll give them the after so they can see the "badcmd" packet. It also
 * gives them control after the data variables are valid, so they can update
 * any kind of automatic thing (say, stroke rate and the like).
 *}
procedure TCodebox.PreprocessPacket(var pak: TRcvPacket);
var
    ok : Boolean;
    msgno: Integer;         { }
    head:  Integer;         { dummy for those packets that we don't care about }
    selno: Integer;         { dummy product detector selector }
    s: String;
begin

    ok := True;

    frmDebug.Prt(Format('Preprocess packet: %s', [ Packet_name(pak)] ) );

    {*-----------------------------------------------------------------------
     * if this is a print ack, dispatch the user's handler immediately.
     *}
    if (pak.RType = RTYPE_PRTACK) and Assigned(FOnPrintACK) then
        FOnPrintACK(Self);

    {*-----------------------------------------------------------------------
     * If we've received a "command" type packet, we always parse it right
     * away into a class variable. This saves the calling routine from having
     * to do this. We also can check for failure of various kinds here and
     * not farther up the line.
     *}
    if pak.RType = RTYPE_CMD then

      case pak.CType of
        CBCMD_RQ_PRINT_ID:
            ok := parse_printer_id(pak, Curr_printer_id);

        CBCMD_RQ_PRINT_CONFIG:
            { if the parse is OK then intercept these values for internal use }
            begin
                ok := parse_printer_config(pak, Curr_printer_config);
                if ok then
                begin
                    Num_heads    := Curr_printer_config.Nheads;
                    Max_num_msg  := Curr_printer_config.Max_msgs;
                    Max_msg_len  := Curr_printer_config.Max_msg_len
                end
            end;

        CBCMD_STROKE_PERIOD:
            ok := parse_stroke_period(pak, Curr_stroke_period);

        CBCMD_SET_DELAY:            { 2.2.1  printer go delay }
            ok := parse_print_go_delay(Pak, head, Curr_print_go_delay);

        CBCMD_SET_FLIGHT_TIME:      { 2.2.5  flight time compensation }
            ok := parse_flight_time(pak, head, Curr_flight_time);

        CBCMD_SEL_P_GO_IN:          { 2.2.6  product detector assignment }
            ok := parse_PD_assign(pak, head, Curr_PD_assign);

        CBCMD_SEL_P_GO_LEVEL:       { 2.2.7  active prod detect level }
            ok := parse_PD_level(pak, selno, Curr_PD_level);

        CBCMD_SEL_P_GO_TIME:        { 2.2.8  prod detect time }
            ok := parse_PD_debounce(Pak, head, Curr_PD_debounce);

        CBCMD_HEAD_ENABLE:          { 2.2.12 head enable }
            ok := parse_head_enable(Pak, head, Curr_head_enable);

        CBCMD_MESSAGE:              { 2.2.14 message storage }
            begin
                ok := parse_message(Pak, msgno, s);
                if (msgno >= 1) and (msgno <= Max_num_msg) then
                    Curr_messages[msgno] := s
            end;

        CBCMD_MESS_REV:             { 2.4.1  reverse message print seq }
            ok := parse_msg_format(Pak, head, Curr_print_formats, cbpMsgReverse);

        CBCMD_MESS_BOLD:            { 2.4.2  print message bold }
            ok := parse_msg_format(Pak, head, Curr_print_formats, cbpBold);

        CBCMD_DOUBLE_SPC:           { 2.4.3  double spaced printing }
            ok := parse_msg_format(Pak, head, Curr_print_formats, cbpDblspace);

        CBCMD_CHAR_REV:             { 2.4.4  reverse individual chars }
            ok := parse_msg_format(Pak, head, Curr_print_formats, cbpCharRev);

        CBCMD_CHAR_INV:             { 2.4.5  inverted printing }
            ok := parse_msg_format(Pak, head, Curr_print_formats, cbpInvert);

        CBCMD_SET_FORMAT:           { 2.4.7  global print format }
            ok := parse_set_format(Pak, head, Curr_print_formats);

        CBCMD_ASSIGN_MESS:          { 2.2.11 message-to-head assignment }
            ok := parse_assign_message(Pak, head, Curr_msg_num);

        CBCMD_CONTIN:               { ?      continuous printing }
            ok := parse_continuous(Pak, head, Curr_contin_enabled,
                                              Curr_contin_pitch);

        CBCMD_STATUS:               { 2.3.2  status request }
            ok := parse_status(Pak, Curr_status);

        CBCMD_STATUS_REPORT_MODE:   { 2.3.1  status reporting mode }        ;
        CBCMD_INIT_CLOCK:           { 2.1.3  printer realtime clock }       ;
        CBCMD_INIT_DATE_MONTHS:     { 2.1.5  read/load month name }         ;
        CBCMD_INIT_DAYS:            { 2.1.6  read/load day name tbl }       ;
        CBCMD_SET_REPEAT:           { 2.2.2  auto-repeat printing }         ;
        CBCMD_SET_AUTOREV:          { 2.2.3  auto-reverse printing }        ;
        CBCMD_SET_ACK:              { 2.2.4  printing ack flags }           ;
        CBCMD_SOFT_P_GO:            { 2.2.9  software print go }            ;
        CBCMD_CLEAR_ALL_MESS:       { 2.2.13 clear all messages }           ;
        CBCMD_PROD_COUNT:           { 2.2.15 product counting }             ;
        CBCMD_SERIAL:               { 2.2.16 read/update serial number }    ;
        CBCMD_CHAR_SET:             { 2.1.7  read/load character set }      ;
        CBCMD_SW_RTC:               { 2.2.17 get software realtime clk }    ;
        CBCMD_BAR_RATIO:            { 2.4.6  barcode thickness ratio }      ;
    {   CBCMD_READ_CHECKSUM:        }       { H.1    read firmware cksums   }
    {   CBCMD_MEMORY_DUMP:          }       { H.2    memory dump            }
    {   CBCMD_DEBUG:                }       { H.4    debug mode             }
        else        ok := False     { unknown packet type - drop it         }
      end;

    { if the parse failed, junk the packet type }
    if not ok then pak.Rtype := RTYPE_BADCMD;

    inherited PreprocessPacket(pak)

end;

{-- if we got a match, turn off the failure counter --}
function TCodebox.got_match(b: Boolean): Boolean;
begin
    Result := b;
    if Result then InitializationFailures := 0
end;

{*----------------------------------------------------------------------
 * Just after we send something, we have go to the corresponding match
 * state. That state is always current+1, and we always break out of
 * the loop.
 *}
procedure TCodebox.enter_match_state(var Finished: Boolean);
begin
    Inc(InitializationState);
    Finished := True
end;

{*
 * matched_input:
 *
 *  This method is used to see if we got a match on the packet we're expecting.
 *  If it doesn't match, we selectively retransmit or wait for a timeout.
 *
 *  The rules are:
 *
 *      - if we have a match, we are for sure done
 *      - if we have too many retries, we fail
 *      - if this is not a timeout, restart the timer and wait for one
 *      - if it is a timeout, then retransmit
 *}
function TCodebox.matched_input(const pk: TRcvPacket; rt:TRcvType;
                                cmd: ShortInt; var Finished:Boolean): Boolean;
begin

    {*----------------------------------------------------------------------
     * if we have a match, return success immediately.
     *}
    if (pk.Rtype = rt) and (pk.Ctype = cmd) then
    begin
        InitializationFailures := 0;
        Result := True
    end
    else
    begin
        Result := False;

        Inc(InitializationFailures);

        {*------------------------------------------------------------------
         * if we have too many failures, we for sure fail.
         *}
        if InitializationFailures >= MaxInitializationFailures then
        begin
            FailInit('Initialization failed with ' + Packet_name(pk));
            Finished := True
        end

        {*------------------------------------------------------------------
         * if this is a timeout, we must suggest a retransmission by going
         * to the previous state.
         *}
        else if pk.Rtype = RTYPE_TIMEOUT then
            Dec(InitializationState)
        else

        {*------------------------------------------------------------------
         * otherwise we got some other kind of packet, so restart the timer
         * so we can be sure the input queue is empty.  We also exit the
         * current state-machine loop.
         *}
        begin
            RestartSendWait;
            Finished := True        { no more looping - wait for response   }
        end
    end
end;

{*-----------------------------------------------------------------------------
 * The Full Inquiry tries to tell us everything we can learn about the printer,
 * and does not actually change any of the parameters. We probably should pass
 * a var paramter of a struct that holds the setup.
 *}
procedure TCodebox.DoTakeSnapshot(h: TCInitEvent; var snap: TSavedCodeboxSetup);
begin
    curr_snap := @snap;
    SetupInit(h, TakeSnapshotHandler, 'DoTakeSnapshot');
end;

procedure TCodebox.TakeSnapshotHandler(Sender: TObject; var pak: TRcvPacket);
var
    nloops   : Integer;
    Finished : Boolean;
begin

    nloops := 0;
    Finished := False;

    while (nloops < 10) and not Finished do
    begin
        Inc(nloops);

        Application.ProcessMessages;

{       frmDebug.Prt(Format('TakeSnapshot:%d', [ InitializationState ] ) ); }

        case InitializationState of
        0:  begin
                InitializationFailures := 0;
                InitializationState    := 10
            end;

        {*--------------------------------------------------------------------
         * REQUEST PRINTER ID
         *}
        10: begin
                NotifyInit('Requesting Printer ID');
                query_printer_id(True);
                enter_match_state(Finished)
            end;

        11: if matched_input(pak, RTYPE_CMD, CBCMD_RQ_PRINT_ID, Finished) then
            begin
                { got printer ID - do something if required }

                InitializationState := 20
            end;

        {*-------------------------------------------------------------------
         * REQUEST PRINTER CONFIGURATION
         *}
        20: begin
                NotifyInit_n('Requesting Printer Configuration', pak.Ctype);
                query_printer_config(True);
                enter_match_state(Finished)
            end;

        21: if matched_input(pak, RTYPE_CMD, CBCMD_RQ_PRINT_CONFIG, Finished) then
            begin
                { got printer configuration }

                InitializationState := 30
            end;

        {*-------------------------------------------------------------------
         * REQUEST PRINT-GO DELAY
         *
         * This is the delay in strokes.
         *}
        30: begin
                NotifyInit_n('Requesting Print Go Delay', pak.Ctype);
                query_print_go_delay(True, Current_head);
                enter_match_state(Finished)
            end;

        31: if matched_input(pak, RTYPE_CMD, CBCMD_SET_DELAY, Finished) then
            begin
                curr_snap^.print_go_delay := Curr_print_go_delay;

                InitializationState := 40
            end;

        {*-------------------------------------------------------------------
         * REQUEST FLIGHT-TIME COMPENSATION
         *}
        40: begin
                NotifyInit_n('Requesting Flight Time Compensation', pak.Ctype);
                query_flight_time(True, Current_head);
                enter_match_state(Finished)
            end;

        41: if matched_input(pak, RTYPE_CMD, CBCMD_SET_FLIGHT_TIME, Finished) then
            begin
                { got the time! }

                InitializationState := 50
            end;

        {*-------------------------------------------------------------------
         * REQUEST PRODUCT-DETECTOR ASSIGNMENT
         *}
        50: begin
                NotifyInit_n('Requesting Product Detector Assignment', pak.Ctype);
                query_PD_assign(True, Current_head);
                enter_match_state(Finished)
            end;

        51: if matched_input(pak, RTYPE_CMD, CBCMD_SEL_P_GO_IN, Finished) then
            begin
                curr_snap^.PD_assign := Curr_PD_assign;

                InitializationState := 60
            end;

        {*-------------------------------------------------------------------
         * REQUEST PRODUCT DETECTOR SIGNAL LEVEL
         *}
        60: begin
                NotifyInit_n('Requesting Product Detector Signal Level', pak.Ctype);
                query_PD_level(True, Curr_setup.CB_PD_Assign);
                enter_match_state(Finished)
            end;

        61: if matched_input(pak, RTYPE_CMD, CBCMD_SEL_P_GO_LEVEL, Finished) then
            begin
                curr_snap^.PD_level := Curr_PD_level;

                InitializationState := 70
            end;

        {*-------------------------------------------------------------------
         * REQUEST PRODUCT DETECTOR DEBOUNCE TIME
         *}
        70: begin
                NotifyInit_n('Requesting Product Detector Debounce Time', pak.Ctype);
                query_PD_debounce(True, Curr_setup.CB_PD_Assign);
                enter_match_state(Finished)
            end;

        71: if matched_input(pak, RTYPE_CMD, CBCMD_SEL_P_GO_TIME, Finished) then
            begin
                curr_snap^.PD_debounce := Curr_PD_debounce;

                InitializationState := 80
            end;

        {*------------------------------------------------------------------
         * REQUEST MESSAGE-TO-HEAD ASSIGNMENT
         *}
        80: begin
                NotifyInit_n('Requesting Message-to-Head Assignment', pak.Ctype);
                query_assign_message(True, Current_head);
                enter_match_state(Finished)
            end;

        81: if matched_input(pak, RTYPE_CMD, CBCMD_ASSIGN_MESS, Finished) then
            begin

                InitializationState := 90
            end;

        {*-------------------------------------------------------------------
         * REQUESTING CONTINUOUS-PRINT STATUS
         *}
        90: begin
                NotifyInit_n('Requesting Continuous status', pak.Ctype);
                query_continuous(True, Current_head);
                enter_match_state(Finished)
            end;

        91: if matched_input(pak, RTYPE_CMD, CBCMD_CONTIN, Finished) then
            begin
                curr_snap^.Contin_enabled := Curr_contin_enabled;
                curr_snap^.Contin_pitch   := Curr_contin_pitch;

                InitializationState := 100
            end;

        {*-------------------------------------------------------------------
         * REQUESTING GLOBAL PRINT FORMATS
         *}
        100:begin
                NotifyInit_n('Requesting Print Formats', pak.Ctype);
                query_format(True, Current_head);
                enter_match_state(Finished)
            end;

        101:if matched_input(pak, RTYPE_CMD, CBCMD_SET_FORMAT, Finished) then
            begin
                curr_snap^.Print_formats := Curr_print_formats;

                InitializationState := 110
            end;

        {*-------------------------------------------------------------------
         * request printer status. This is a bit more work because we have to
         * keep asking until we get a current status (it's "historical" before
         * that).
         *}
        110: begin
                curr_snap^.nsetups := 0;
                InitializationState := 111
             end;
        111: begin
                NotifyInit_n('Getting printer status', pak.Ctype);
                query_status(True, cbkHistorical);
                enter_match_state(Finished)
             end;

        112: if matched_input(pak, RTYPE_CMD, CBCMD_STATUS, Finished) then
                with curr_snap^ do
                begin
                    frmDebug.Prt('status');

                    if nsetups < 16 then
                    begin
                        { Inc(nsetups); }
                        { Setups[nsetups] := Curr_status; }
                        Finished := False;
                        if Curr_status.era = cbkHistorical then
                            InitializationState := 111  { ask again }
                        else
                            InitializationState := 999  { done! }
                    end
                end
              else
                frmDebug.Prt('No match on status');

        {*-------------------------------------------------------------------
         * FINISHED!
         *}
        999 :begin
                SuccessInit_n('FullInquiry Successful', pak.Ctype);
                Finished := True;
            end

        else ECodeboxError.Create(
                    Format('Bogus state %d in FullInquiryHandler',
                            [ InitializationState ] ) )
        end

    end;

    if not Finished then
        ECodeboxError.Create('FullInquiryHandler had too many loops!')

end;

{*-----------------------------------------------------------------------------------------------
 *
 *}
procedure TCodebox.DoJobSetup(h: TCInitEvent; const job: TCodeboxJob);
begin
    CurrentJob := job;              { save copy of job }
    SetupInit(h, JobSetupHandler, 'DoJobSetup')
end;

procedure TCodebox.JobSetupHandler(Sender: TObject; var pak: TRcvPacket);
var
    nloops  : Integer;
    Finished: Boolean;

    l_msg, l_id, l_wid: ShortInt;       { used in parse_serial }
    l_num: LongInt;

begin

    Finished := False;
    nloops   := 0;

    while  not Finished   and  (nloops < 10)  do
    begin
        Inc(nloops);

        with CurrentJob do
        case InitializationState of
        {*------------------------------------------------------------------
         *
         *}
        0:  begin
                InitializationFailures := 0;
                InitializationState    := 10
            end;

        {*------------------------------------------------------------------
         * SET MESSAGE
         *
         * This downloads the job's message into the appropriate message slot
         *}
        10: begin
                NotifyInit(Format('Setting message to slot %d', [msgno]));
                set_message(True, msgno, msg);
                enter_match_state(Finished)
            end;

        11: if matched_input(pak, RTYPE_ACK, 0, Finished) then
            begin
                { message is downloaded OK }

                { go to next state }
                InitializationState := 20
            end;

        {*------------------------------------------------------------------
         * ASSIGN SERIAL NUMBER
         *
         * If this job is serialized -- nearly all cabling jobs are -- we
         * need to send down the proper serial number. We have found that
         * this is not very reliable, so we have to send down a request for
         * the current serial number, then use it to set ours (this gets the
         * width correct).
         *}
        20: if not CurrentJob.Serialized then
                InitializationState := 30
            else
            begin
                NotifyInit('Querying for Serial Number format');
                query_serial(True, msgno, 1);
                enter_match_state(Finished)
            end;

        21: if matched_input(pak, RTYPE_CMD, CBCMD_SERIAL, Finished)
                and parse_serial(pak, l_msg, l_id, l_num, l_wid) then
            begin
                NotifyInit(Format('Setting start serial number %d [w%d]',
                    [startser, l_wid]));
                set_serial(True, msgno, 1, startser, l_wid);
                enter_match_state(Finished);
            end;

        22: if matched_input(pak, RTYPE_ACK, 0, Finished) then
            begin
                { serial number programmed properly! }

                InitializationState := 30
            end;

        {*-------------------------------------------------------------------
         * SET GLOBAL PRINT FORMAT
         *
         * This sets the combination of bold/reverse/etc. for printing
         *}
        30: begin
                NotifyInit('Setting global print format');
                set_format(True, headno, [cbpMsgReverse]);
                enter_match_state(Finished)
            end;

        31: if matched_input(pak, RTYPE_ACK, 0, Finished) then
            begin
                { print format set OK }

                InitializationState := 40
            end;

        {*-------------------------------------------------------------------
         * ASSIGN MESSAGE TO HEAD
         *}
        40: begin
                NotifyInit(Format('Assigning msg %d->head %d', [headno, msgno]));
                set_assign_message(True, headno, msgno);
                enter_match_state(Finished)
            end;

        41: if matched_input(pak, RTYPE_ACK, 0, Finished) then
            begin
                { message assigned! }

                InitializationState := 50
            end;

        {*-------------------------------------------------------------------
         * ASSIGN PRODUCT DETECTOR TO HEAD
         *}
        50: begin
                NotifyInit(Format('Assigning Product Detector %d to head %d',
                                  [Curr_setup.CB_PD_Assign, Current_head]));
                set_PD_assign(True, Current_head, Curr_setup.CB_PD_Assign);
                enter_match_state(Finished)
            end;

        51: if matched_input(pak, RTYPE_ACK, 0, Finished) then
            begin
                { product detector is assigned }

                InitializationState := 99
            end;

        {*-------------------------------------------------------------------
         * Finished!
         *}
        99: begin
                SuccessInit('Ready to Run');
                Finished := True
            end;

        else ECodeboxError.Create(Format('Bogus state %d in JobSetupHandler',
                                         [ InitializationState ] ) )
        end
    end;

    if not Finished then
        ECodeboxError.Create('JobSetupHandler has too many init loops!')
end;

{*----------------------------------------------------------------------------
 * initial setup is done once we know what kind of printer we have.  We always
 * disable the product detectors so we don't print anything while other stuff
 * is going on.
 *}
procedure TCodebox.DoRunJob(h: TCInitEvent);
begin
    SetupInit(h, RunJobHandler, 'DoRunHandler')
end;

procedure TCodebox.RunJobHandler(Sender: TObject; var pak: TRcvPacket);
var
    nloops   : Integer;
    Finished : Boolean;

begin

    Finished := False;
    nloops   := 0;

    while not Finished  and (nloops < 10) do
    begin
        Inc(nloops);

        case InitializationState of
        0:  begin
                InitializationFailures := 0;
                InitializationState    := 10
            end;

        {*-------------------------------------------------------------------
         * ENABLE HARDWARE PRODUCT DETECTOR
         *}
        10: begin
                NotifyInit('Assigning Hardware Product Detector');
                set_PD_assign(True, Current_head, Curr_setup.CB_PD_Assign);
                enter_match_state(Finished)
            end;

        11: if matched_input(pak, RTYPE_ACK, 0, Finished) then
            begin
                { product detector assigned! }

                InitializationState := 99
            end;

        {*-------------------------------------------------------------------
         * Finished!
         *}
        99: begin
                SuccessInit('Job Startup is Successful');
                Finished := True
            end;

        else
            ECodeboxError.Create(Format('Bogus state %d in InitialSetupHandler',
                                        [ InitializationState ] ) )
        end
    end;

    if not Finished then
        ECodeboxError.Create('JobRunHandler had too many loops!')
end;

{*-------------------------------------------------------------------------
 * This is the module that does the first-level initialization of the printer.
 * There are all kinds of things we have to do here to get this right, so we
 * have built a rather large state machine to handle this reasonably.
 *}
procedure TCodebox.DoInitialSetup(h: TCInitEvent);
begin
    SetupInit(h, InitialSetupHandler, 'DoInitialSetup');
end;

procedure TCodebox.InitialSetupHandler(Sender: TObject; var pak: TRcvPacket);
var
    nloops  : Integer;
    Finished: Boolean;

begin
    nloops   := 0;
    Finished := False;

    while not Finished  and  (nloops < 10) do
    begin
        Inc(nloops);

        case InitializationState of
        {*-------------------------------------------------------------------
         * we always enter the initialization machine with state 0, so
         * immediately enter our first interesting state.
         *}
        0:  begin
                InitializationFailures := 0;
                InitializationState := 10
            end;

        {*-------------------------------------------------------------------
         * REQUESTING PRINTER ID
         *
         * First we have to request the printer's ID and get the response.
         * Currently there is nothing special done when we receive the
         * printer's ID, though we probably should.
         *}
{SEND}  10: begin
                NotifyInit('Requesting Printer ID');
                query_printer_id(True);
                enter_match_state(Finished)
            end;

{MATCH} 11: if matched_input(pak, RTYPE_CMD, CBCMD_RQ_PRINT_ID, Finished) then
            begin
                { got printer ID - do something if required }

                { internal transit to next state }
                InitializationState := 20
            end;

        {*-------------------------------------------------------------------
         * REQUESTING PRINTER CONFIGURATION
         *
         * ask the printer about its current configuration, including # of
         * heads and the like.
         *}
{SEND}  20: begin
                NotifyInit_n('Requesting Printer Configuration', pak.Ctype);
                query_printer_config(True);
                enter_match_state(Finished)
            end;

{MATCH} 21: if matched_input(pak, RTYPE_CMD, CBCMD_RQ_PRINT_CONFIG, Finished) then
            begin
                { got printer config - do something if required }

                InitializationState := 30
            end;

        {*-------------------------------------------------------------------
         * DISABLE HARDWARE PRODUCT DETECTOR
         *
         * Since we're initializing, we must tell the printer to stop printing
         * by disabling the hardware product detectors. This might not be
         * required because the Printmaster is probably not generating any
         * print-go signals, but we want to be certain.
         *}
{SEND}  30: begin
                NotifyInit_n('Disabling Hardware Product Detector', pak.Ctype);
                set_PD_assign(True, Current_head, 0);
                enter_match_state(Finished)
            end;

{MATCH} 31: if matched_input(pak, RTYPE_ACK, 0, Finished) then
            begin
                { product detectors are disabled -- do something if required }

                InitializationState := 40;
            end;

        {*-------------------------------------------------------------------
         * DISABLE UNSOLICTED STATUS REPORTING
         *
         * Eventually we will certainly turn this on, but for now we can't
         * take the printer sending us status when we don't expect it. Sorry.
         *}
{SEND}  40: begin
                NotifyInit('Disabling Unsolicited Status Mode');
                set_status_mode(True, False, [cbsSerial,cbsFault,cbsInk]);
                enter_match_state(Finished)
            end;

{MATCH} 41: if matched_input(pak, RTYPE_ACK, 0, Finished) then
            begin
                { status mode is off - do something if appropriate }

                InitializationState := 50
            end;

        {*-------------------------------------------------------------------
         * ENABLE PRINTING ACKNOWLEDGEMENTS
         *
         * We want to use the print-acknowledgements from the printer, but
         * since these have proven to be unreliably sent, we only use them
         * for limited purposes. Still, we'll take them when we can.
         *}
{SEND}  50: begin
                NotifyInit('Enabling Printing Acknowledgements');
                set_print_ack(True, Current_head, Char($1C));
                enter_match_state(Finished)
            end;

{MATCH} 51: if matched_input(pak, RTYPE_ACK, 0, Finished) then
            begin
                { print acknowledgements are now on }

                InitializationState := 60;
            end;

        {*-------------------------------------------------------------------
         * DISABLE AUTO-REVERSE MODE
         *
         * We never need auto-reverse mode for our stuff. It will almost
         * never be turned on, but we want to make sure...
         *}
{SEND}  60: begin
                NotifyInit('Disabling Auto-Reverse Mode');
                set_autoreverse(True, Current_head, 0);
                enter_match_state(Finished)
            end;

{MATCH} 61: if matched_input(pak, RTYPE_ACK, 0, Finished) then
            begin
                { auto-repeat is disabled - do something if required }

                InitializationState := 70
            end;

        {*-------------------------------------------------------------------
         * DISABLE CONTINUOUS PRINT MODE
         *
         * Continuous print mode is used by the Codebox when it's run with
         * the Oyster hand terminal, and we absolutely cannot use it in our
         * Impresor mode.
         *}
{SEND}  70: begin
                NotifyInit('Disabling Continuous Print Mode');
                set_continuous(True, Current_head, {Enabled?}False, {pitch?}0);
                enter_match_state(Finished)
            end;

{MATCH} 71: if matched_input(pak, RTYPE_ACK, 0, Finished) then
            begin
                { continuous mode now disabled }

                InitializationState := 80
            end;

        {*-------------------------------------------------------------------
         * SET PRODUCT DETECTOR DEBOUNCE
         *
         * ===NOTE: not sure if we really need to do this?
         *}
{SEND}  80: begin
                NotifyInit('Setting Product Detect Debounce');
                with Curr_setup do
                    set_PD_debounce(True, CB_PD_Assign, CB_PD_Debounce);
                enter_match_state(Finished)
            end;

        81: if matched_input(pak, RTYPE_ACK, 0, Finished) then
            begin
                { debounce is set }

                InitializationState := 90
            end;

        {*-------------------------------------------------------------------
         * SET PRODUCT DETECTOR SIGNAL LEVEL
         *
         * Set the product detector signal level to that required by the
         * user's setup screen.
         *}
        90: begin
                NotifyInit('Setting Product Detect Level');
                with Curr_setup do
                    set_PD_level(True, CB_PD_Assign, CB_PD_Level);
                enter_match_state(Finished)
            end;

        91: if matched_input(pak, RTYPE_ACK, 0, Finished) then
            begin
                { product detector level set OK }

                InitializationState := 100
            end;

        {*-------------------------------------------------------------------
         * set the Codebox clock to the current time.
         *}
        100:begin
                NotifyInit('Setting Codebox Clock');
                set_realtime_clk_now(True);
                enter_match_state(Finished)
            end;

        101: if matched_input(pak, RTYPE_ACK, 0, Finished) then
            begin
                { Codebox clock is set }
                InitializationState := 999
            end;

        {*-------------------------------------------------------------------
         * FINISHED! No more stuff to do!
         *}
{DONE}  999:begin
                SuccessInit('Codebox OK');
                Finished := True
            end

        else ECodeboxError.Create(
                    Format('Bogus state %d in InitialSetupHandler',
                                [ InitializationState ] ) )
        end
    end;

    if not Finished then
        ECodeboxError.Create('InitialSetupHandler had too many loop!')
end;

end.