OpenCores
URL https://opencores.org/ocsvn/pdp8/pdp8/trunk

Subversion Repositories pdp8

[/] [pdp8/] [trunk/] [pdp8/] [cpu/] [cpu.new] - Rev 2

Compare with Previous | Blame | View Log

--------------------------------------------------------------------------------
--!
--! PDP8 Processor
--!
--! \brief
--!      Processor
--!
--! \details
--!      I hope you like state machines because this is implemented as one big
--!      state machine.
--!
--! \file
--!      cpu.vhd
--!
--! \author
--!      Rob Doyle - doyle (at) cox (dot) net
--!
--------------------------------------------------------------------------------
--
--  Copyright (C) 2009, 2010, 2011, 2012 Rob Doyle
--
-- This source file may be used and distributed without restriction provided
-- that this copyright statement is not removed from the file and that any
-- derivative work contains the original copyright notice and the associated
-- disclaimer.
--
-- This source file is free software; you can redistribute it and/or modify it
-- under the terms of the GNU Lesser General Public License as published by the
-- Free Software Foundation; version 2.1 of the License.
--
-- This source is distributed in the hope that it will be useful, but WITHOUT
-- ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS
-- FOR A PARTICULAR PURPOSE. See the GNU Lesser General Public License for more
-- details.
--
-- You should have received a copy of the GNU Lesser General Public License
-- along with this source; if not, download it from
-- http://www.gnu.org/licenses/lgpl.txt
--
--------------------------------------------------------------------------------
--
-- Comments are formatted for doxygen
--

library ieee;                                   --! IEEE Library
use ieee.std_logic_1164.all;                    --! IEEE 1164
use ieee.numeric_std.all;                       --! IEEE Numeric Standard
use work.cpu_types.all;
-- synthesis translate_off
use std.textio.all;
use ieee.std_logic_textio.all;
use work.pck_fio.all;
-- synthesis translate_on

--
--! eCPU Entity
--

entity eCPU is port (
    sys     : in  sys_t;                        --! Clock/Reset
    swCPU   : in  swCPU_t;                      --! CPU Configuration
    swOPT   : in  swOPT_t;                      --! Options Configuration
    swDATA  : in  swDATA_t;                     --! Data Switch Inputs
    swCNTL  : in  swCNTL_t;                     --! Control Switch Inputs
    dev     : in  dev_t;                        --! Device Output
    cpu     : out cpu_t                         --! CPU Output
);
end eCPU;

--
--! eCPU RTL
--

architecture rtl of eCPU is

    --
    -- Registers
    --

    signal LAC      : ldata_t;                  --! Link and Accumulator
    alias  L        : std_logic is LAC (0);     --! Link Bit
    alias  AC       : data_t is LAC(1 to 12);   --! Accumulator
    signal IR       : data_t;                   --! Instruction Register
    signal PC       : addr_t;                   --! Program Counter
    signal MA       : addr_t;                   --! Memory Address Register
    signal MB       : data_t;                   --! Memory Buffer (output)
    signal MD       : data_t;                   --! Memory Data Register (input)
    signal MQ       : data_t;                   --! MQ Register
    signal MQA      : data_t;                   --! MQA Register
    signal SC       : sc_t;                     --! SC Register
    signal SP1      : addr_t;                   --! Stack Pointer
    signal SP2      : addr_t;                   --! Stack Pointer
    signal SR       : data_t;                   --! Switch Register

    --
    -- Register Operation
    --

    signal acOP     : acOP_t;                   --! AC operation
    signal pcOP     : pcOP_t;                   --! PC operation
    signal irOP     : irOP_t;                   --! IR operation
    signal maOP     : maOP_t;                   --! MA operation
    signal mbOP     : mbOP_t;                   --! MB operation
    signal mqOP     : mqOP_t;                   --! MQ operation
    signal mqaOP    : mqaOP_t;                  --! MQA operation
    signal scOP     : scOP_t;                   --! SC operation
    signal sp1OP    : spOP_t;                   --! SP1 operation
    signal sp2OP    : spOP_t;                   --! SP2 operation
    signal srOP     : srOP_t;                   --! SR operation

    --
    -- Memory Extension Control Registers
    --

    signal IB       : field_t;                  --! Instruction Buffer
    signal INF      : field_t;                  --! Instruction Field
    signal DF       : field_t;                  --! Data Field
    signal SF       : sf_t;                     --! Save Field
    signal UB       : std_logic;                --! User Buffer Flag
    signal UF       : std_logic;                --! User Flag

    --
    -- Memory Extension Control Register Operations
    --

    signal ibOP     : ibOP_t;                   --! IB operation
    signal ifOP     : ifOP_t;                   --! IF operation
    signal dfOP     : dfOP_t;                   --! DF operation
    signal sfOP     : sfOP_t;                   --! SF operation
    signal ubOP     : ubOP_t;                   --! User Buffer operation
    signal ufOP     : ufOP_t;                   --! USER Flag operation
    signal IRQ      : std_logic;                --! IRQ Flag

    --
    -- BTSTRP:
    --

    signal BTSTRP   : std_logic;                --! BTSTRP Flag
    signal btstrpOP : btstrpOP_t;               --! BTSTRP operation

    --
    -- CTRLFF:
    -- The Control Panel Flip-Flop (CTRLFF), is set when the CPREQ is granted.
    -- CTRLFF prevents further CPREQs from being granted, bypasses the
    -- interrupt enable system and redefines several of the internal control
    -- instructions.  As long as the CTRLFF is set, LXPAR is used for all
    -- instruction, direct data and indirect pointer references.  Also, while
    -- CTRLFF is set, the INTGNT line is held inactive but the Interrupt Grant
    -- Flip Flop is not cleared.  IOTs executed while CTRLFF is set do not clear
    -- the Interrupt grant flip flop.
    --

    signal CTRLFF   : std_logic;                --! CTRLFF
    signal ctrlffOP : ctrlffOP_t;               --! CTRLFF operation

    --
    -- EAE:
    -- EAE Long Operations
    --

    signal EAE      : eae_t;                    --! EAE Register
    signal eaeOP    : eaeOP_t;                  --! EAE operation

    --
    -- EMODE:
    -- The EMODE bit is set at reset and is set by the SWAB and cleared by the
    -- SWBA instructions.  This enables EAE Mode A and EAE Mode B instructions.
    --

    signal EMODE    : std_logic;                --! EAE Mode
    signal emodeOP  : emodeOP_t;                --! EAE Mode operation

    --
    -- FZ:
    -- The Force Zero Flag (FZ) is used to implement Extended memory operations
    -- for Panel Mode instructions.  When set, forces control panel instruction
    -- field access to field zero.  Indirect data accesses are not affected.
    --

    signal FZ       : std_logic;                --! Force Zero
    signal fzOP     : fzOP_t;                   --! FZ operation

    --
    -- HLTTRP:
    -- The HLTTRP flip-flop allows the cpu to single step through code.
    -- The HLTTRP flip-flop is set by a HLT instruction.
    --

    signal HLTTRP   : std_logic;                --! HLTTRP Flip-Flop
    signal hlttrpOP : hlttrpOP_t;               --! HLTTRP operation

    --
    -- GTF:
    --

    signal GTF      : std_logic;                --! Greater than Flag
    signal gtfOP    : gtfOP_t;                  --! GTF operation

    --
    -- ID:
    -- The Interrupt Enable Delay Flip-Flop (ID) delays the effect of the ION
    -- instruction until the instruction after the ION instruction has executed.
    -- This will allow a return from interrupt to be executed before the next
    -- interrupt request is serviced.
    --

    signal ID       : std_logic;                --! ION Delay Flip-flop
    signal idOP     : idOP_t;                   --! ION Delay Operation

    --
    -- IE:
    -- The Interrupt Enable Flip-Flop (IE) enables and disables interrupts.
    --

    signal IE       : std_logic;                --! Interrupt Enable
    signal ieOP     : ieOP_t;                   --! IE operation

    --
    -- II:
    -- The Interrupt Inhibit (II) Flip-Flop is set whenever there is an
    -- instruction executed that could change the Instruction Field.  These
    -- include CIF, CDI, RMF, RTF, CAF, CUF, SUF.  The II Flip-Flop is
    -- cleared when the next JMP, JMS, RTN1, or RTN2 instruction is executed.
    -- This prevents an interrupt from occuring between the CIF (or like)
    -- instruction and the return (or like) instruction.
    --

    signal II       : std_logic;                -- Interrupt Inhibit Flip-Flop
    signal iiOP     : iiOP_t;                   -- Interrupt Inhibit Operation

    --
    -- PDF:
    -- The Panel Data Flag (PDF) is used to contol whether indirectly addressed
    -- data references by Control Panel AND, TAD, ISZ or DCA instructions
    -- reference panel memory or main memory.  If PDF is set, this flag causes
    -- indirect references from control panel memory to address control panel
    -- memory by asserting LXPAR.  If PDF is cleared, this flag causes indirect
    -- references from control panel memory to address main memory by asserting
    -- LXMAR.  The PDF is cleared unconditionally whenever the panel mode is
    -- entered for any reason.  It is also cleared by the Clear Panel Data
    -- (CPD) instruction.  The PDF is set by the Set Panel Data (SPD)
    -- instruction. The state of the Panel Data flag is ignored when not
    -- operating in panel mode.
    --

    signal PDF      : std_logic;                --! Panel Data Flag
    signal pdfOP    : pdfOP_t;                  --! PDF operation

    --
    -- PEX:
    -- The Panel Exit Delay (PEX) Flip-Flop is set by the PEX instruction.
    -- When a JMP, JMS, RET1, or RET2 instruction is executed with the PEX
    -- Flip-Flop set, the CPU will exit panel mode.  The PEX Flip-Flop is
    -- cleared by the JMP, JMS, RET1, or RET2 instruction.
    --

    signal PEX      : std_logic;                -- PEX Flip-Flop
    signal pexOP    : pexOP_t;                  -- PEX Operation

    --
    -- PNLTRP:
    -- A Panel Trap is one of the many ways to enter panel mode.  The Panel Trap
    -- Flip-Flop (PNLTRP) is set by any of the PR0, PR1, PR2, PR3 instructions.
    -- The PNLTRP flag can be examined and cleared by the PRS instruction.
    --

    signal PNLTRP   : std_logic;                --! PNLTRP Flag
    signal pnltrpOP : pnltrpOP_t;               --! PNLTRP operation

    --
    -- PRWON:
    -- The Power-On Trap Flip-Flop (PWRTRP) is set when STRTUP is negated during
    -- RESET, The Power-On Flip-Flop (PWRTRP) is reset by a PRS or PEX
    -- instruction.
    --

    signal PWRTRP   : std_logic;                --! PWRTRP Flip-Flop
    signal pwrtrpOP : pwrtrpOP_t;               --! PWRTRP operation

    --
    -- USRTRP:
    -- User Mode Trap.
    --

    signal USRTRP   : std_logic;                --! USR Interrupt
    signal usrtrpOP : usrtrpOP_t;               --! USR Interrupt operation

    --
    -- XMA
    --

    signal XMA      : field_t;                  --! XMA Register
    signal xmaOP    : xmaOP_t;                  --! XMA operation

    --
    -- Bus Control Signals
    --

    signal busb     : busOP_t;                  --! Bus Operation output
    signal busOP    : busOP_t;                  --! Bus Operation input
    signal ioclrb   : std_logic;                --! IOCLR register output
    signal ioclrOP  : std_logic;                --! IOCLR register input
    signal wrb      : std_logic;                --! WR signal register input
    signal wrOP     : std_logic;                --! WR signal register output
    signal rdb      : std_logic;                --! RD signal register output
    signal rdOP     : std_logic;                --! RD signal register input
    signal ifetchb  : std_logic;                --! IFETCH signal register output
    signal ifetchOP : std_logic;                --! IFETCH signal register input
    signal datafb   : std_logic;                --! DATAF signal register output
    signal datafOP  : std_logic;                --! DATAF signal register input
    signal lxdarb   : std_logic;                --! LXDAR signal register output
    signal lxdarOP  : std_logic;                --! LXDAR signal register input
    signal lxmarb   : std_logic;                --! LXMAR signal register output
    signal lxmarOP  : std_logic;                --! LXMAR signal register input
    signal lxparb   : std_logic;                --! LXPAR signal register output
    signal lxparOP  : std_logic;                --! LXPAR signal register input
    signal memselb  : std_logic;                --! MEMSEL signal register output
    signal memselOP : std_logic;                --! MEMSEL signal register input
    signal intgntb  : std_logic;                --! INTGNT signal register output
    signal dmagnt   : std_logic;                --! DMAGNT signal register input
    signal intgntOP : std_logic;                --! INTGNT signal register input
    signal waitfb   : std_logic;                --! WAITF signal register output
    signal waitfOP  : std_logic;                --! WAITF signal register input

    signal oops     : std_logic;
    
    --
    -- State Information
    --

    type state_t is (
        stateReset,
        stateInit,
        stateCheckReq,
        stateFetchAddr,
        stateFetchData,
        stateLoadIR,
        stateDecodeInstruction,

        --
        -- MRI States
        --

        stateMRIreadAddr,
        stateMRIreadDataIND,
        stateMRIreadIncAddr,
        stateMRIreadIndData,
        stateMRIexecute,

        --
        -- IOT states
        --

        stateIOTdecode,
        stateIOT,

        --
        -- Stack Operation States
        --

        statePOPaddr,
        statePOPdata,
        stateRTN1,
        stateRTN2,
        stateRTNaddr,
        stateRTNdata,

        --
        -- OPR Groups
        --

        stateOprGroup1Seq3,
        stateOprGroup1Seq4,
        stateOprGroup2Seq2,
        stateOprGroup3Seq3,

        --
        -- Front Panel States
        --

        stateHalt,
        stateContinue,
        stateLoadADDR,
        stateLoadEXTD,
        stateClear,
        stateDepositWriteData,
        stateDeposit,
        stateExamine,
        stateExamineReadAddr,
        stateExamineReadData,
        stateHaltDone,

        --
        -- EAE States
        --

        stateEAEfetchAddr,
        stateEAEfetchData,
        stateEAEindWrite,
        stateEAEindReadAddr,
        stateEAEindReadData,
        stateEAEshift,
        stateEAEwait,
        stateEAEnmi,
        stateEAEshiftDVI,
        stateEAEsubDVI,
        stateEAEmuy,
        stateEAEreadDADaddr0,
        stateEAEreadDADaddr1,
        stateEAEreadDADdata0,
        stateEAEreadDADdata1,
        stateEAEdst,

        --
        -- HALT states
        --

        stateDone,
        stateLALA
    );


    signal   state      : state_t;
    signal   nextState  : state_t;
    constant maAutoIncr : std_logic_vector(3 to 11) := o"001";

    --
    -- Output files for state dumpState
    --

    -- synthesis translate_off
    file     FIL        : text is out "STD_OUTPUT";
    file     STDOUT     : text is out "STD_OUTPUT";
  --file     FIL        : text is out "trace.txt";
    -- synthesis translate_on

    --
    -- vectorize
    --

    function vectorize(s: std_logic) return std_logic_vector is
        variable v: std_logic_vector(0 to 0);
    begin
        v(0) := s;
        return v;
    end;

    --
    -- dumpState()
    --

    procedure dumpState(PC : in addr_t) is
        -- synthesis translate_off
        variable LIN : line;
        -- synthesis translate_on
    begin
        -- synthesis translate_off
        write (LIN, string'("ST:"));
        write (LIN, string'(" PC="));
        owrite(LIN, PC);
        write (LIN, string'(", IR="));
        owrite(LIN, IR);
        write (LIN, string'(", LAC="));
        owrite(LIN, "00" & LAC);
        write (LIN, string'(", MQ="));
        owrite(LIN, MQ);
        write (LIN, string'(", SR="));
        owrite(LIN, SR);
        write (LIN, string'(", IF="));
        owrite(LIN, INF);
        write (LIN, string'(", DF="));
        owrite(LIN, DF);
        write (LIN, string'(", IB="));
        owrite(LIN, IB);
        write (LIN, string'(", UB="));
        owrite(LIN, "00" & vectorize(UB));
        write (LIN, string'(", UF="));
        owrite(LIN, "00" &  vectorize(UF));
        write (LIN, string'(", USF="));
        owrite(LIN, "00" &  SF(0 to 0));
        write (LIN, string'(", ISF="));
        owrite(LIN, SF(1 to 3));
        write (LIN, string'(", DSF="));
        owrite(LIN, SF(4 to 6));
        write (LIN, string'(", SC="));
        owrite(LIN, '0' & SC);
        write (LIN, string'(", GTF="));
        owrite(LIN, "00" & vectorize(GTF));
        write (LIN, string'(", EMODE="));
        owrite(LIN, "00" & vectorize(EMODE));
        write (LIN, string'(", IEFF="));
        owrite(LIN, "00" & vectorize(IE));
        write (LIN, string'(", IDFF="));
        owrite(LIN, "00" & vectorize(ID));
        write (LIN, string'(", IIFF="));
        owrite(LIN, "00" & vectorize(II));
        write (LIN, string'(", IRQ="));
        owrite(LIN, "00" & vectorize(IRQ));
        write (LIN, string'(", SP1="));
        owrite(LIN, SP2);
        write (LIN, string'(", SP2="));
        owrite(LIN, SP1);
        write (LIN, string'("; MA=00000"));
        --owrite(LIN, XMA & MA);
        writeline(FIL, LIN);
        -- synthesis translate_on
    end dumpState;

    --
    -- dispHALT
    --

    procedure dispHALT(signal PC : in addr_t) is
        -- synthesis translate_off
       variable LIN : line;
        -- synthesis translate_on
    begin
        -- synthesis translate_off
        write (LIN, string'("CPU Halted at PC = "));
        owrite(LIN, PC);
        writeline(STDOUT, LIN);
        -- synthesis translate_on
    end dispHALT;

    --
    -- dispCONT
    --

    procedure dispCONT(signal PC : in addr_t) is
        -- synthesis translate_off
        variable LIN : line;
        -- synthesis translate_on
    begin
        -- synthesis translate_off
        write (LIN, string'("CPU Continued at PC = "));
        owrite(LIN, PC);
        writeline(STDOUT, LIN);
        -- synthesis translate_on
    end dispCONT;

begin

    IRQ <= '1' when ((dev.intr = '1') or
                     (USRTRP = '1' and swOPT.TSD = '0') or
                     (usrtrpOP = usrtrpopSET and swOPT.TSD = '0')) else '0';

    --
    --  ALU
    --

    iALU : entity work.eALU (rtl) port map (
        sys     => sys,
        acOP    => acOP,
        BTSTRP  => BTSTRP,
        GTF     => GTF,
        HLTTRP  => HLTTRP,
        IE      => IE,
        IRQ     => IRQ,
        PNLTRP  => PNLTRP,
        PWRTRP  => PWRTRP,
        DF      => DF,
        EAE     => EAE,
        INF     => INF,
        IR      => IR,
        MA      => MA,
        MD      => MD,
        MQ      => MQ,
        SC      => SC,
        SF      => SF,
        SP1     => SP1,
        SP2     => SP2,
        SR      => SR,
        UF      => UF,
        LAC     => LAC
    );

    --
    -- CTRLFF
    --

    iCTRLFF : entity work.eCTRLFF (rtl) port map (
        sys      => sys,
        ctrlffOP => ctrlffOP,
        CTRLFF   => CTRLFF
    );

    --
    -- EAE Register
    --

    iEAE : entity work.eEAE (rtl) port map (
        sys     => sys,
        eaeOP   => eaeOP,
        MD      => MD,
        MQ      => MQ,
        AC      => AC,
        EAE     => EAE
    );

    --
    -- EAE Mode A
    --

    iEMODE : entity work.eEMODE (rtl) port map (
        sys     => sys,
        emodeOP => emodeOP,
        EMODE   => EMODE
    );

    --
    -- FZ Flip Flop
    --

    iFZ : entity work.eFZ (rtl) port map (
        sys  => sys,
        fzOP => fzOP,
        FZ   => FZ
    );

    --
    -- GTF
    --

    iGTF : entity work.eGTF (rtl) port map (
        sys   => sys,
        gtfOP => gtfOP,
        AC    => AC,
        GTF   => GTF
    );

    --
    -- HLTTRP
    --

    iHLTTRP : entity work.eHLTTRP (rtl) port map (
        sys      => sys,
        hlttrpOP => hlttrpOP,
        HLTTRP   => HLTTRP
    );

    --
    -- Program Counter (PC)
    --

    iPC : entity work.ePC (rtl) port map (
        sys  => sys,
        pcOP => pcOP,
        IR   => IR,
        MA   => MA,
        MB   => MB,
        MD   => MD,
        SR   => SR,
        PC   => PC
    );

    --
    -- Multiplier Quotient Register (MQ)
    --

    iMQ : entity work.eMQ (rtl) port map (
        sys  => sys,
        mqOP => mqOP,
        AC   => AC,
        MD   => MD,
        EAE  => EAE,
        MQ   => MQ
    );

    --
    -- Auxillary Multiplier Quotient Register (MQA)
    --

    iMQA : entity work.eMQA (rtl) port map (
        sys   => sys,
        mqaOP => mqaOP,
        MQ    => MQ,
        MQA   => MQA
    );

    --
    -- Interrupt Enable Flip-Flop
    --

    iIE : entity work.eIE (rtl) port map (
        sys  => sys,
        ieOP => ieOP,
        IE   => IE
    );

    --
    -- Interrupt Inhibit Flip-Flop
    --

    iII : entity work.eII (rtl) port map (
        sys  => sys,
        iiOP => iiOP,
        II   => II
    );

    --
    -- USRTRP Flip-Flop
    --

    iUSRTRP : entity work.eUSRTRP (rtl) port map (
        sys      => sys,
        usrtrpOP => usrtrpOP,
        USRTRP   => USRTRP
    );

    --
    -- Instruction Register (IR)
    --

    iIR: entity work.eIR (rtl) port map (
        sys   => sys,
        irOP  => irOP,
        MD    => MD,
        IR    => IR
    );

    --
    -- Memory Address Register (MA)
    --

    iMA : entity work.eMA (rtl) port map (
        sys  => sys,
        maOP => maOP,
        IR   => IR,
        MB   => MB,
        MD   => MD,
        PC   => PC,
        SP1  => SP1,
        SP2  => SP2,
        SR   => SR,
        MA   => MA
    );

    --
    -- Memory Buffer Register (MB)
    --

    iMB : entity work.eMB (rtl) port map (
        sys  => sys,
        mbOP => mbOP,
        AC   => AC,
        MA   => MA,
        MD   => MD,
        MQ   => MQ,
        PC   => PC,
        SR   => SR,
        MB   => MB
    );

    --
    -- Instruction Buffer Address Extension Register (IB)
    --

    iIB : entity work.eIB (rtl) port map (
        sys  => sys,
        ibOP => ibOP,
        SF   => SF,
        AC   => AC,
        IR   => IR,
        IB   => IB
    );

    --
    -- Instruction Field Address Extension Register (IF/INF)
    --

    iIF : entity work.eIF (rtl) port map (
        sys  => sys,
        ifOP => ifOP,
        IB   => IB,
        SR   => SR,
        INF  => INF
    );

    --
    -- ION Delay Flip-Flop
    --

    iID : entity work.eID (rtl) port map (
        sys  => sys,
        idOP => idOP,
        ID   => ID
    );

    --
    -- Data Field Address Extension Register (DF)
    --

    iDF : entity work.eDF (rtl) port map (
        sys  => sys,
        dfOP => dfOP,
        AC   => AC,
        IR   => IR,
        SF   => SF,
        SR   => SR,
        DF   => DF
    );

    --
    -- BTSTRP Flip-Flop
    --

    iBTSTRP : entity work.eBTSTRP (rtl) port map (
        sys      => sys,
        btstrpOP => btstrpOP,
        BTSTRP   => BTSTRP
    );

    --
    -- PDF Flip-Flop
    --

    iPDF : entity work.ePDF (rtl) port map (
        sys   => sys,
        pdfOP => pdfOP,
        PDF   => PDF
    );

    --
    -- PEX Flip-Flop
    --

    iPEX : entity work.ePEX (rtl) port map (
        sys   => sys,
        pexOP => pexOP,
        PEX   => PEX
    );

    --
    -- PNLTRP Flip-Flop
    --

    iPNLTRP : entity work.ePNLTRP (rtl) port map (
        sys      => sys,
        pnltrpOP => pnltrpOP,
        PNLTRP   => PNLTRP
    );

    --
    -- PWRTRP Flip-Flop
    -- When set during reset, the unit will enter panel mode before executing
    -- the first instruction.
    --

    iPWRTRP : entity work.ePWRTRP (rtl) port map (
        sys      => sys,
        pwrtrpOP => pwrtrpOP,
        PWRTRP   => PWRTRP
    );

    --
    -- SC
    -- Step Counter
    --

    iSC : entity work.eeSC (rtl) port map (
        sys  => sys,
        scOP => scOP,
        AC   => AC,
        MD   => MD,
        SC   => SC
    );

    --
    -- SF
    -- Save Field Address Extension Register (SF)
    --

    iSF : entity work.eSF (rtl) port map (
        sys  => sys,
        sfOP => sfOP,
        DF   => DF,
        IB   => IB,
        UB   => UB,
        SF   => SF
    );

    --
    -- SP1
    -- Stack Pointer #1
    --

    iSP1 : entity work.eSP (rtl) port map (
        sys  => sys,
        spOP => sp1OP,
        AC   => AC,
        SP   => SP1
    );

    --
    -- SP2
    -- Stack Pointer #2
    --

    iSP2: entity work.eSP (rtl) port map (
        sys  => sys,
        spOP => sp2OP,
        AC   => AC,
        SP   => SP2
    );

    --
    -- SR
    -- Switch Register
    --

    iSR : entity work.eSR (rtl) port map (
        sys   => sys,
        swCPU => swCPU,
        srOP  => srOP,
        AC    => AC,
        SRD   => swDATA,
        SR    => SR
    );

    --
    -- UB
    -- User Buffer Flag
    --

    iUB : entity work.eUB (rtl) port map (
        sys  => sys,
        ubOP => ubOP,
        AC5  => AC(5),
        SF0  => SF(0),
        UB   => UB
    );

    --
    -- UF
    -- User Flag
    --

    iUF : entity work.eUF (rtl) port map (
        sys  => sys,
        ufOP => ufOP,
        UB   => UB,
        UF   => UF
    );

    --
    -- XMA
    -- XMA is disabled by disabling the KM8E option
    --

    iXMA : entity work.eXMA (rtl) port map (
        sys   => sys,
        xmaOP => xmaOP,
        sWCPU => swCPU,
        DF    => DF,
        INF   => INF,
        IB    => IB,
        XMA   => XMA
    );

    --
    -- Next State Decoder
    --

    process(swOPT, dev, IRQ, state, USRTRP, AC, L, MQA,
            BTSTRP, CTRLFF, EMODE, GTF, HLTTRP, ID, IE, II,
            LAC, MA, MD, MQ, PC, PEX, PNLTRP, PWRTRP, IR, SC, UF, swCPU,
            swCNTL.halt, swCNTL.clear, swCNTL.exam, swCNTL.dep, swCNTL.lock,
            swCNTL.step, swCNTL.cont, swCNTL.loadADDR, swCNTL.loadEXTD)

        variable EAEIR : std_logic_vector(0 to 3);

    begin

        --
        -- Control signal defaults
        --

        busOP      <= busopNOP;
        ioclrOP    <= '0';
        wrOP       <= '0';
        rdOP       <= '0';
        ifetchOP   <= '0';
        datafOP    <= '0';
        lxdarOP    <= '0';
        memselOP   <= '0';
        intgntOP   <= '0';

        --
        -- Operation defaults
        --

        acOP       <= acopNOP;
        busOP      <= busopNOP;
        btstrpOP   <= btstrpopNOP;
        ctrlffOP   <= ctrlffopNOP;
        dfOP       <= dfopNOP;
        eaeOP      <= eaeopNOP;
        emodeOP    <= emodeopNOP;
        fzOP       <= fzopNOP;
        gtfOP      <= gtfopNOP;
        hlttrpOP   <= hlttrpopNOP;
        idOP       <= idopNOP;
        ieOP       <= ieopNOP;
        iiOP       <= iiopNOP;
        ibOP       <= ibopNOP;
        ifOP       <= ifopNOP;
        irOP       <= iropNOP;
        maOP       <= maopNOP;
        mbOP       <= mbopNOP;
        mqOP       <= mqopNOP;
        mqaOP      <= mqaopNOP;
        pcOP       <= pcopNOP;
        pdfOP      <= pdfopNOP;
        pexOP      <= pexopNOP;
        pnltrpOP   <= pnltrpopNOP;
        pwrtrpOP   <= pwrtrpopNOP;
        scOP       <= scopNOP;
        sfOP       <= sfopNOP;
        sp1OP      <= spopNOP;
        sp2OP      <= spopNOP;
        srOP       <= sropNOP;
        ubOP       <= ubopNOP;
        ufOP       <= ufopNOP;
        usrtrpOP   <= usrtrpopNOP;
        xmaOP      <= xmaopNOP;

        --
        -- Default Next State
        --

        nextState <= stateLALA;

        --
        -- BTSTRP set when CPREQ is asserted
        --

        if dev.cpreq = '1' and swCPU = swHD6120 then
            btstrpOP <= btstrpOPSET;
        end if;

        --
        -- The State Machine
        --

        case state is

            --
            -- Reset State
            --

            when stateRESET =>
                busOP     <= busopRESET;
                nextState <= stateInit;

            --
            --
            -- Startup States
            --

            when stateInit =>
                if swCPU = swHD6120 then

                    --
                    -- HD6120 Mode with STARTUP asserted.
                    -- Boot to front panel mode (PC=7777)
                    --

                    if swOPT.STARTUP = '1' then
                        pwrtrpOP  <= pwrtrpopSET;
                        nextState <= stateCheckReq;

                    --
                    -- HD6120 Mode with STARTUP negated.
                    -- Begin executing at PC=0000
                    --

                    else
                        pwrtrpOP  <= pwrtrpopCLR;
                        nextState <= stateCheckReq;

                    end if;
                else

                    --
                    -- PDP8 Mode with STARTUP asserted.
                    -- Set PC to contents of switch register and start
                    -- execution.
                    --

                    if swOPT.STARTUP = '1' then
                        pcOP      <= pcopSR;
                        nextState <= stateFetchAddr;

                    --
                    -- PDP8 Mode with STARTUP negated.
                    -- Start in HALT state.  User must interact with front
                    -- panel.
                    --

                    else
                        nextState <= stateHalt;

                    end if;
                end if;

            --
            -- This state occurs at the very top of the processing loop.
            -- The priority hierarchy is:
            -- 1.  RESET -   Clears Accummulator and Link registers and clears the
            --               RUN output signal.
            -- 2.  CPREQ -   If not RESET and CPREQ is asserted, the processor
            --               enters Panel Mode.
            -- 3.  RUN/HLT - If neither RESET or CPREQ is asserted and HLT is
            --               asserted (HLTFLAG = '1'), the processor should enter
            --               the HALT state and the end of the current cycle.
            -- 4.  DEV.INTR -  If no higher priority signal is asserted and IRQ is
            --               asserted an interrup may be processed.
            --

            when stateCheckReq =>

                --
                -- HD6120:
                -- Panel mode is entered because of the occurrence of any of
                -- four events.  Each of these events sets a status flag, as
                -- well as causing the entry into panel mode. It should be
                -- noted that more than one event might happen simultaneously.
                --
                -- These events are:
                --  1. PWRTRP  - Power-up Trap
                --  2. PNLTRP  - Panel Trap
                --  3. HLTTRP  - HLT insruction
                --  4. BTSTRP  - CPREQ asserted.
                --  5. Not already in panel mode
                --
                -- When a panel request is granted, the PC is stored in
                -- location 0000 of the control panel memory and the CPU
                -- resumes operation at location 7777 (octal) of the panel
                -- memory. During the PC write, 0 appears on EMA0, EMA1 and
                -- EMA2. The states of the IB, IF/INF, OF, ISF and DSF
                -- registers are not disturbed by entry into the control
                -- panel mode but execution is forced to commence in field
                -- zero.
                --
                -- See also description of ID, IE, and II.
                --

                if (((swCPU = swHD6120) and (ID = '0') and (II = '0') and (CTRLFF = '0') and (PWRTRP = '1')) or
                    ((swCPU = swHD6120) and (ID = '0') and (II = '0') and (CTRLFF = '0') and (PNLTRP = '1')) or
                    ((swCPU = swHD6120) and (ID = '0') and (II = '0') and (CTRLFF = '0') and (BTSTRP = '1')) or
                    ((swCPU = swHD6120) and (ID = '0') and (II = '0') and (CTRLFF = '0') and (HLTTRP = '1'))) then

                    ctrlffOP  <= ctrlffopSET;
                    fzOP      <= fzopSET;
                    pdfOP     <= pdfopCLR;
                    maOP      <= maop0000;
                    mbOP      <= mbopPC;
                    pcOP      <= pcop7777;
                    xmaOP     <= xmaopCLR;
                    busOP     <= busopWRZF;
                    assert false report "---------------------> Panel Trap <---------------------" severity note;
                    nextState <= stateFetchAddr;

                --
                -- HALT Mode is entered if the HLTTRP is set or the RUN/HALT
                -- Switch is in the HALT position.
                --

                elsif (((swCPU /= swHD6120) and (HLTTRP = '1')) or
                       ((swCPU /= swHD6120) and (swCNTL.halt = '1') and (swCNTL.lock = '0')) or
                       ((swCPU /= swHD6120) and (swCNTL.step = '1') and (swCNTL.lock = '0'))) then
                    hlttrpOP  <= hlttrpopCLR;
                    dispHALT(PC);
                    nextState <= stateHalt;

                --
                -- Interrupt Request
                -- When an External Interrupt is asserted, the following occurs:
                --   1.  The PC is stored in location 0000 of field 0.
                --   2.  The Interrupt Enable Flip-Flop (IE) is disabled
                --       which precludes automatically nested interupts.
                --   3.  The INTGNT signal is is asserted.
                --   4.  UF, IF/INF, DF is loaded into SF.
                --   5.  IF/INF is cleared.
                --   6.  IB is cleared.
                --   7.  DF is cleared.
                --   8.  UF is cleared.
                --   9.  UB is cleared.
                --  10.  The PC is set to "0001" of main memory field 0 so
                --       that the next instruction is fetched from there.
                --
                -- See also description of ID, IE, and II.
                --

                elsif (IRQ = '1') and (ID = '0') and (IE = '1') and (II = '0') then
                    intgntOP  <= '1';
                    maOP      <= maop0000;
                    mbOP      <= mbopPC;
                    ieOP      <= ieopCLR;
                    sfOP      <= sfopUBIBDF;
                    dfOP      <= dfopCLR;
                    ifOP      <= ifopCLR;
                    ibOP      <= ibopCLR;
                    ufOP      <= ufopCLR;
                    ubOP      <= ubopCLR;
                    pcOP      <= pcop0001;
                    xmaOP     <= xmaopCLR;
                    busOP     <= busopWRZF;
                    assert false report "---------------------> Interrupt <---------------------" severity note;
                    nextState <= stateFetchAddr;

                --
                -- No interrupts, halt, single step, or anthing else.
                -- Just start to fetch the next instruction.
                --

                else
                    nextState <= stateFetchAddr;

                end if;

            --
            -- HALT State
            -- An HD6120 will never get to this state since halts are trapped
            -- by the front panel.
            --

            when stateHalt =>

                --
                -- Continue Switch Pressed
                --

                if ((swCNTL.cont = '1' and swCNTL.lock = '0') or
                    (swCNTL.step = '1' and swCNTL.lock = '0')) then
                    dispCONT(PC);
                    nextState <= stateContinue;

                --
                -- Load Address Switch Pressed
                -- This sets MA and PC to the contents of the switch register.
                --  MA <- SR
                --  PC <- SR
                --

                elsif swCNTL.loadADDR = '1' and swCNTL.lock = '0' then
                    pcOP      <= pcopSR;
                    maOP      <= maopSR;
                    nextState <= stateLoadADDR;

                --
                -- Load Extended Address Switch Pressed
                -- This sets IF and DF to the contents of the switch register.
                --  IF <- SR[6:8]
                --  DF <- SR[9:11]
                --

                elsif swCNTL.loadEXTD = '1' and swCNTL.lock = '0' then
                    ifOP      <= ifopSR6to8;
                    dfOP      <= dfopSR9to11;
                    nextState <= stateLoadEXTD;

                --
                -- Clear Switch Pressed
                --

                elsif swCNTL.clear = '1' and swCNTL.lock = '0' then
                    acOP      <= acopCLACLL;
                    mqOP      <= mqopCLR;
                    ifOP      <= ifopCLR;
                    dfOP      <= dfopCLR;
                    sp1OP     <= spopCLR;
                    sp2OP     <= spopCLR;
                    gtfOP     <= gtfopCLR;
                    emodeOP   <= emodeopCLR;
                    ieOP      <= ieopCLR;
                    idOP      <= idopSET;
                    usrtrpOP  <= usrtrpopCLR;
                    busOP     <= busopIOCLR;
                    nextState <= stateClear;

                --
                -- Examine Switch Pressed
                -- This loads the contents of the memory location addressed by
                -- the MA register into the MD register and increments the MA
                -- and PC registers.
                --  MD <- MEM[IF'MA]
                --  

                elsif swCNTL.exam = '1' and swCNTL.lock = '0' then
                    maOP      <= maopPC;
                    xmaOP     <= xmaopIF;
                    busOP     <= busopRDIFaddr;
                    nextState <= stateExamineReadAddr;

                --
                -- Deposit Switch Pressed
                -- This writes the contents of the Switch Register into the
                -- memory location addressed by the MA register.
                --  MEM[IF'MA] <- SR
                --

                elsif swCNTL.dep = '1' and swCNTL.lock = '0' then
                    maOP      <= maopPC;
                    mbOP      <= mbopSR;
                    xmaOP     <= xmaopIF;
                    busOP     <= busopWRIF;
                    nextState <= stateDepositWriteData;

                else
                    nextState <= stateHalt;

                end if;

            --
            -- Wait for Continue button to negate
            --

            when stateContinue =>
                if swCNTL.cont = '1' then
                    nextState <= stateContinue;
                else
                    nextState <= stateFetchAddr;
                end if;

            --
            -- Wait for LoadADDR button to negate
            --

            when stateLoadADDR =>
                if swCNTL.loadADDR = '1' then
                    nextState <= stateLoadADDR;
                else
                    nextState <= stateHaltDone;
                end if;

            --
            -- Wait for LoadEXTD button to negate
            --

            when stateLoadEXTD =>
                if swCNTL.loadEXTD = '1' then
                    nextState <= stateLoadEXTD;
                else
                    nextState <= stateHaltDone;
                end if;

            --
            -- Wait for Clear button to negate
            --

            when stateClear =>
                if swCNTL.clear = '1' then
                    nextState <= stateClear;
                else
                    nextState <= stateHaltDone;
                end if;

            --
            -- Examine Read Addr
            -- This is the address phase of the read cycle.
            --  MD <- MEM[IF'MA]
            --

            when stateExamineReadAddr =>
                xmaOP     <= xmaopIF;
                busOP     <= busopRDIFdata;
                nextState <= stateExamineReadData;

            --
            -- Examine Read Data
            -- This is the data phase of the read cycle.
            -- At the end of this cycle, MD will have the data that was read.
            -- This state increments the PC and MA register after the examine.
            --  MD <- MEM[IF'MA]
            --  MA <- MA + 1
            --  PC <- PC + 1
            --

            when stateExamineReadData =>
                maOP      <= maopINC;
                pcOP      <= pcopINC;
                nextState <= stateExamine;

            --
            -- Wait for Examine button to negate
            --

            when stateExamine =>
                if swCNTL.exam = '1' then
                    nextState <= stateExamine;
                else
                    nextState <= stateHaltDone;
                end if;

            --
            -- This cycle writes data to memory.  Once written
            -- this state increments PC and MA.
            --  MA <- MA + 1
            --  PC <- PC + 1
            --

            when stateDepositWriteData =>
                maOP      <= maopINC;
                pcOP      <= pcopINC;
                nextState <= stateDeposit;

            --
            -- Wait for Deposit button to negate
            --

            when stateDeposit =>
                if swCNTL.dep = '1' then
                    nextState <= stateDeposit;
                else
                    nextState <= stateHaltDone;
                end if;

            --
            -- Update Front Panel display
            --

            when stateHaltDone =>
                nextState <= stateHalt;

            --
            -- Begin Instruction Fetch.  Perform Read Address Cycle.
            --  MA <- PC
            --  MD <- MEM[IF'MA]
            --

            when stateFetchAddr =>
                maOP      <= maopPC;
                xmaOP     <= xmaopIF;
                busOP     <= busopFETCHaddr;
                nextState <= stateFetchData;

            --
            -- Continue Instruction Fetch.  Perform Read Data Cycle.
            -- The Interrupt Enable Delay Flip-Flop (ID) is cleared.
            -- If the ID was set at the beginning of this instruction,
            -- an interrupt, if present, was deferred.  We clear it now.
            -- Therefore this instruction will complete and then that
            -- interrupt, if present, will be recognized.
            --  MD <- MEM[IF'MA]
            --

            when stateFetchData =>
                pcOP      <= pcopINC;
                idOP      <= idopCLR;
                xmaOP     <= xmaopIF;
                busOP     <= busopFETCHdata;
                nextState <= stateLoadIR;

            --
            -- Load IR with the instruction that was fetched.
            -- Note: This state is a wasted state.  We could have decoded the MD
            -- and loaded the IR simultaneously.
            --  IR <- MD
            --

            when stateLoadIR =>
                irOP      <= iropMD;
                nextState <= stateDecodeInstruction;

            --
            -- Decode Instruction in IR
            --

            when stateDecodeInstruction =>

                --
                -- Default Next State
                --

                nextState <= stateLALA;

                --
                -- Parse OPCODE
                --

                case IR(0 to 2) is

                    --
                    -- AND Instruction
                    --

                    when opAND =>

                        case IR(3 to 4) is

                            --
                            -- AND, direct, zero page.  Start Read Addr Cycle
                            --  MA <- 00000'IR(5:11)
                            --

                            when amDZ =>
                                maOP      <= maopZP;
                                xmaOP     <= xmaopIF;
                                busOP     <= busopRDIFaddr;
                                nextState <= stateMRIreadAddr;

                            --
                            -- AND, direct, curr page.  Start Read Addr Cycle
                            --  MA <- MA(0:4)'IR(5:11)
                            --

                            when amDC =>
                                maOP      <= maopCP;
                                xmaOP     <= xmaopIF;
                                busOP     <= busopRDIFaddr;
                                nextState <= stateMRIreadAddr;

                            --
                            -- AND, indirect, zero page.  Start Read Addr Cycle
                            --  MA <- 00000'IR(5:11)
                            --

                            when amIZ =>
                                maOP      <= maopZP;
                                xmaOP     <= xmaopIF;
                                busOP     <= busopRDIFaddr;
                                nextState <= stateMRIreadAddr;

                            --
                            -- AND, indirect, curr page.  Start Read Addr Cycle
                            --  MA <- MA(0:4)'IR(5:11)
                            --

                            when amIC =>
                                maOP      <= maopCP;
                                xmaOP     <= xmaopIF;
                                busOP     <= busopRDIFaddr;
                                nextState <= stateMRIreadAddr;

                            --
                            -- Everthing else
                            --

                            when others =>
                                null;

                        end case;

                    --
                    -- TAD Instruction
                    --

                    when opTAD =>

                        case IR(3 to 4) is

                            --
                            -- TAD, direct, zero page.  Start Read Addr Cycle
                            --  MA <- 00000'IR(5:11)
                            --

                            when amDZ =>
                                maOP      <= maopZP;
                                xmaOP     <= xmaopIF;
                                busOP     <= busopRDIFaddr;
                                nextState <= stateMRIreadAddr;

                            --
                            -- TAD, direct, curr page.  Start Read Addr Cycle
                            --  MA <- MA(0:4)'IR(5:11)
                            --

                            when amDC =>
                                maOP      <= maopCP;
                                xmaOP     <= xmaopIF;
                                busOP     <= busopRDIFaddr;
                                nextState <= stateMRIreadAddr;

                            --
                            -- TAD, indirect, zero page.  Start Read Addr Cycle
                            --  MA <- 00000'IR(5:11)
                            --

                            when amIZ =>
                                maOP      <= maopZP;
                                xmaOP     <= xmaopIF;
                                busOP     <= busopRDIFaddr;
                                nextState <= stateMRIreadAddr;

                            --
                            -- TAD, indirect, curr page.  Start Read Addr Cycle
                            --  MA <- MA(0:4)'IR(5:11)
                            --

                            when amIC =>
                                maOP      <= maopCP;
                                xmaOP     <= xmaopIF;
                                busOP     <= busopRDIFaddr;
                                nextState <= stateMRIreadAddr;

                            --
                            -- Everything else
                            --

                            when others =>
                                null;

                        end case;

                    --
                    -- ISZ Instruction
                    --

                    when opISZ =>

                        case IR(3 to 4) is

                            --
                            -- ISZ, direct, zero page.  Start Read Addr Cycle
                            --  MA <- 00000'IR(5:11)
                            --

                            when amDZ =>
                                maOP      <= maopZP;
                                xmaOP     <= xmaopIF;
                                busOP     <= busopRDIFaddr;
                                nextState <= stateMRIreadAddr;

                            --
                            -- ISZ, direct, curr page.  Start Read Addr Cycle
                            --  MA <- MA(0:4)'IR(5:11)
                            --

                            when amDC =>
                                maOP      <= maopCP;
                                xmaOP     <= xmaopIF;
                                busOP     <= busopRDIFaddr;
                                nextState <= stateMRIreadAddr;

                            --
                            -- ISZ, indirect, zero page.  Start Read Addr Cycle
                            --  MA <- 00000'IR(5:11)
                            --

                            when amIZ =>
                                maOP      <= maopZP;
                                xmaOP     <= xmaopIF;
                                busOP     <= busopRDIFaddr;
                                nextState <= stateMRIreadAddr;

                            --
                            -- ISZ, indirect, curr page.  Start Read Addr Cycle
                            --  MA <- MA(0:4)'IR(5:11)
                            --

                            when amIC =>
                                maOP      <= maopCP;
                                xmaOP     <= xmaopIF;
                                busOP     <= busopRDIFaddr;
                                nextState <= stateMRIreadAddr;

                            --
                            -- Everything else
                            --

                            when others =>
                                null;

                        end case;

                    --
                    -- MRI DCA
                    --

                    when opDCA =>

                        case IR(3 to 4) is

                            --
                            -- DCA, direct, zero page.  Start Write Cycle
                            --  MA <- 00000'IR(5:11)
                            --

                            when amDZ =>
                                wrOP      <= '1';
                                acOP      <= acopCLA;
                                maOP      <= maopZP;
                                mbOP      <= mbopAC;
                                xmaOP     <= xmaopIF;
                                busOP     <= busopRDIFaddr;
                                nextState <= stateDone;

                            --
                            -- DCA, direct, curr page.  Start Write Cycle
                            --  MA <- MA(0:4)'IR(5:11)
                            --

                            when amDC =>
                                wrOP      <= '1';
                                acOP      <= acopCLA;
                                maOP      <= maopCP;
                                mbOP      <= mbopAC;
                                xmaOP     <= xmaopIF;
                                busOP     <= busopRDIFaddr;
                                nextState <= stateDone;

                            --
                            -- DCA, indirect, zero page.  Start Read Addr Cycle.
                            --  MA <- 00000'IR(5:11)
                            --

                            when amIZ =>
                                maOP      <= maopZP;
                                xmaOP     <= xmaopIF;
                                busOP     <= busopRDIFaddr;
                                nextState <= stateMRIreadAddr;

                            --
                            -- DCA, indirect, curr page.  Start Read Addr Cycle.
                            --  MA <- MA(0:4)'IR(5:11)
                            --

                            when amIC =>
                                maOP      <= maopCP;
                                xmaOP     <= xmaopIF;
                                busOP     <= busopRDIFaddr;
                                nextState <= stateMRIreadAddr;

                            --
                            -- Everything else
                            --

                            when others =>
                                 null;

                        end case;
                        
                    --
                    -- JMS Instruction
                    --

                    when opJMS =>

                        --
                        -- The II Flip-Flop is cleared.
                        -- The FZ Flip-Flop is cleared
                        --
                        
                        iiOP <= iiopCLR;
                        fzOP <= fzopCLR;

                        case IR(3 to 4) is

                            --
                            -- JMS, direct, zero page.  Start write cycle.
                            --  MA <- 00000'IR(5:11)
                            --
                            -- When the PEX Flip-flop is set, the CPU shall
                            -- exit from Panel Mode to Main Memory (i.e., clear
                            -- CTRLFF) during the next JMP, JMS, RTN1 or RTN2
                            -- instruction.
                            --
                            -- PEX is cleared by the JMP, JMS, RTN1 or RTN2
                            -- instruction. 
                            --

                            when amDZ =>
                                ifOP      <= ifopIB;
                                ufOP      <= ufopUB;
                                maOP      <= maopZP;
                                mbOP      <= mbopPC;
                                pcOP      <= pcopZPP1;
                                xmaOP     <= xmaopIB;
                                busOP     <= busopWRIB;
                                if PEX = '1' then
                                    ctrlffOP <= ctrlffopCLR;
                                    pexOP    <= pexopCLR;
                                end if;
                                nextState <= stateDone;

                            --
                            -- JMS, direct, curr page.  Start write cycle.
                            --  MA <- MA(0:4)'IR(5:11)
                            --
                            -- When the PEX Flip-flop is set, the CPU shall
                            -- exit from Panel Mode to Main Memory (i.e., clear
                            -- CTRLFF) during the next JMP, JMS, RTN1 or RTN2
                            -- instruction.
                            --
                            -- PEX is cleared by the JMP, JMS, RTN1 or RTN2
                            -- instruction. 
                            --

                            when amDC =>
                                ifOP      <= ifopIB;
                                ufOP      <= ufopUB;
                                maOP      <= maopCP;
                                mbOP      <= mbopPC;
                                pcOP      <= pcopCPP1;
                                xmaOP     <= xmaopIB;
                                busOP     <= busopWRIB;
                                if PEX = '1' then
                                    ctrlffOP <= ctrlffopCLR;
                                    pexOP    <= pexopCLR;
                                end if;
                                nextState <= stateDone;

                            --
                            -- JMS, indirect, zero page.  Start Read Addr Cycle.
                            --  MA <- 00000'IR(5:11)
                            --

                            when amIZ =>
                                maOP      <= maopZP;
                                xmaOP     <= xmaopIF;
                                busOP     <= busopRDIFaddr;
                                nextState <= stateMRIreadAddr;

                            --
                            -- JMS, indirect, curr page.  Start Read Addr Cycle.
                            --  MA <- MA(0:4)'IR(5:11)
                            --

                            when amIC =>
                                maOP      <= maopCP;
                                xmaOP     <= xmaopIF;
                                busOP     <= busopRDIFaddr;
                                nextState <= stateMRIreadAddr;

                            --
                            -- Everthing else
                            --

                            when others =>
                                null;

                        end case;

                    --
                    -- JMP Instruction
                    --

                    when opJMP =>

                        --
                        -- The II Flip-Flop is cleared.
                        -- The FZ Flip-Flop is cleared
                        --
                        
                        iiOP <= iiopCLR;
                        fzOP <= fzopCLR;

                        case IR(3 to 4) is

                            --
                            --
                            -- JMP, direct, zero page.
                            --  MA <- 00000'IR(5:11)
                            --
                            -- When the PEX Flip-flop is set, the CPU shall
                            -- exit from Panel Mode to Main Memory (i.e., clear
                            -- CTRLFF) during the next JMP, JMS, RTN1 or RTN2
                            -- instruction.
                            --
                            -- PEX is cleared by the JMP, JMS, RTN1 or RTN2
                            -- instruction. 
                            --

                            when amDZ =>
                                maOP <= maopZP;
                                pcOP <= pcopZP;
                                ifOP <= ifopIB;
                                ufOP <= ufopUB;
                                if PEX = '1' then
                                    ctrlffOP <= ctrlffopCLR;
                                    pexOP    <= pexopCLR;
                                end if;
                                nextState <= stateDone;

                            --
                            -- JMP, direct, curr page.
                            --  MA <- MA(0:4)'IR(5:11)
                            --
                            -- When the PEX Flip-flop is set, the CPU shall
                            -- exit from Panel Mode to Main Memory (i.e., clear
                            -- CTRLFF) during the next JMP, JMS, RTN1 or RTN2
                            -- instruction.
                            --
                            -- PEX is cleared by the JMP, JMS, RTN1 or RTN
                            -- instruction. 
                            --

                            when amDC =>
                                maOP <= maopCP;
                                pcOP <= pcopCP;
                                ifOP <= ifopIB;
                                ufOP <= ufopUB;
                                if PEX = '1' then
                                    ctrlffOP <= ctrlffopCLR;
                                    pexOP    <= pexopCLR;
                                end if;
                                nextState <= stateDone;

                            --
                            -- JMP, indirect, zero page.  Start Read Addr Cycle.
                            --  MA <- 00000'IR(5:11)
                            --

                            when amIZ =>
                                maOP      <= maopZP;
                                xmaOP     <= xmaopIF;
                                busOP     <= busopRDIFaddr;
                                nextState <= stateMRIreadAddr;

                            --
                            -- JMP, indirect, curr page.  Start Read Addr Cycle.
                            --  MA <- MA(0:4)'IR(5:11)
                            --

                            when amIC =>
                                maOP      <= maopCP;
                                xmaOP     <= xmaopIF;
                                busOP     <= busopRDIFaddr;
                                nextState <= stateMRIreadAddr;

                            --
                            -- Everything else
                            --

                            when others =>
                                null;

                        end case;

                    --
                    -- IOT Instructions
                    --

                    when opIOT =>

                        --
                        -- Default Next State
                        --

                        nextState <= stateDone;

                        --
                        -- Handle USR Mode interrupts
                        --

                        if (UF = '1') then

                            usrtrpOP  <= usrtrpopSET;
                            nextState <= stateDone;

                        else

                            --
                            -- Internal IOT (CPU Control)
                            --   600x, 62xx are internal IOTs
                            --

                            case IR(0 to 11) is

                                --
                                -- OP 6000: PRS/SKON
                                --

                                when o"6000" =>

                                    --
                                    -- HD6120 only
                                    -- OP 6000: PRS - Panel Read Status Word.
                                    -- Read panel status bits into AC<0-4>, 0
                                    -- into AC<5:11>.  Following the reading of
                                    -- the flags into the AC, the flags are
                                    -- cleared, with the exception of HLTTRP.
                                    -- BTSTR is cleared only if a 1 was read
                                    -- into AC<0>.
                                    --

                                    if swCPU = swHD6120 then
                                        if CTRLFF = '1' then
                                            acOP     <= acopPRS;
                                            pnltrpOP <= pnltrpopCLR;
                                            pwrtrpOP <= pwrtrpopCLR;
                                            btstrpOP <= btstrpopCLR;
                                        end if;

                                    --
                                    -- PDP-8/E and later and HD-6120
                                    -- SKON - Skip if interupt system is on,
                                    -- turn it off.
                                    --

                                    elsif ((swCPU = swPDP8E) or
                                           (swCPU = swPDP8F) or
                                           (swCPU = swPDP8A) or
                                           (swCPU = swHD6120)) then
                                        if IE = '1' then
                                            pcOP <= pcopINC;
                                        end if;
                                        ieOP <= ieopCLR;

                                    --
                                    -- Pre PDP8/E
                                    -- This instruction was a NOP.
                                    --

                                    else
                                        null;

                                    end if;

                                --
                                -- IOT 6001: ION - Enable Interrupts.
                                -- The Interrupt Enable Flip-Flop (IE) is set.
                                -- The Interrupt Enable Delay Flip-Flop (ID)
                                -- is set.
                                --
                                -- Note: Setting the ID delays the interrupt
                                -- enable by one instruction so that a return
                                -- (from interrupt) may be executed before the
                                -- next interrupt request is serviced.
                                --

                                when o"6001" =>
                                    ieOP <= ieopSET;
                                    idOP <= idopSET;

                                --
                                -- IOT 6002: IOF - Disable Interrupts
                                -- The Interrupt Enable Flip Flop (IE) is cleared
                                -- immediately. If IRQ is low while this
                                -- instruction is being processed, the interrupt
                                -- will not be recognized.
                                --

                                when o"6002" =>
                                    ieOP <= ieopCLR;

                                --
                                -- OP 6003: PGO/SRQ
                                --

                                when o"6003" =>

                                    --
                                    -- HD6120 only
                                    -- OP 6003: PGO - Panel Go.
                                    --

                                    if swCPU = swHD6120 then
                                        if CTRLFF = '1' then
                                            hlttrpOP <= hlttrpopCLR;
                                        end if;

                                    --
                                    -- PDP-8/E and later and HD-6120
                                    -- OP 6003: SRQ - Skip on Interupt Request
                                    --

                                    elsif ((swCPU = swPDP8E) or
                                           (swCPU = swPDP8F) or
                                           (swCPU = swPDP8A) or
                                           (swCPU = swHD6120)) then
                                        if IRQ = '1' then
                                            pcOP <= pcopINC;
                                        end if;

                                    --
                                    -- Pre PDP-8/E
                                    -- OP 6003: ION - This was equivalent to
                                    -- the ION instruction.
                                    --

                                    else
                                        ieOP <= ieopSET;
                                        idOP <= idopSET;

                                    end if;

                                --
                                -- IOT 6004: PEX/GTF
                                --
                                -- GTF - Get Flags
                                --
                                --  00 01 02 03 04 05 06 07 08 09 10 11
                                -- +--+--+--+--+--+--+--------+--------+
                                -- | L|GT|IR|0 |IE|UF|   IF   |   DF   |
                                -- +--+--+--+--+--+--+--------+--------+
                                --
                                -- L  - The link bit.
                                -- GT - The Greater Than bit
                                -- IR - The interrupt request status, as tested by SRQ.
                                -- IE - The state of the interrupt enable flip-flop (IE)
                                -- UF - User Flag
                                -- IF - The instruction field.
                                -- DF - The data field.
                                --
                                -- PEX -  Panel Exit to Normal Mode 
                                -- Exit from panel mode into main memory at the end
                                -- of the next JMP, JMS, RTN1 or RTN2 instruction.
                                --

                                when o"6004" =>

                                    --
                                    -- OP 6004: PEX - Panel Exit to Normal Mode
                                    -- HD6120 in Panel Mode only
                                    --
                                    -- Set PEX Flip-flop
                                    -- Clear PWRTRP and PNLTRP.
                                    --

                                    if swCPU = swHD6120 and CTRLFF = '1' then
                                        pwrtrpOP <= pwrtrpopCLR;
                                        pnltrpOP <= pnltrpopCLR;
                                        pexOP    <= pexopSET;

                                    --
                                    -- OP 6004: GTF - Get Flags
                                    -- HD6120 in Normal Mode only
                                    -- AC(4) is always set.
                                    -- AC(5) is always cleared.
                                    --

                                    elsif swCPU = swHD6120 and CTRLFF = '0' then
                                        acOP <= acopGTF1;

                                    --
                                    -- OP 6004: GTF - Get Flags
                                    -- PDP-8/E and later with KM8E installed
                                    -- AC(4) is set to state of the interrupt
                                    --

                                    elsif ((swCPU = swPDP8E and swOPT.KM8E = '1') or
                                           (swCPU = swPDP8F and swOPT.KM8E = '1') or
                                           (swCPU = swPDP8A and swOPT.KM8E = '1')) then
                                        acOP <= acopGTF2;

                                    --
                                    -- Pre PDP-8/E
                                    -- OP 6004: This was and ADC operation or a
                                    -- NOP.
                                    --

                                    else
                                        null;

                                    end if;

                                --
                                -- IOT 6005: RTF - Restore Flags and Fields from AC.
                                -- The flags are set as follows:
                                --
                                --  00 01 02 03 04 05 06 07 08 09 10 11
                                -- +--+--+--+--+--+--+--------+--------+
                                -- | L|GT|  |  |IE|UB|   IB   |   DF   |
                                -- +--+--+--+--+--+--+--------+--------+
                                --

                                when o"6005" =>
                                    if ((swCPU = swPDP8E) or
                                        (swCPU = swPDP8F) or
                                        (swCPU = swPDP8A) or
                                        (swCPU = swHD6120)) then

                                        --
                                        -- HD6120: The AC is cleared following
                                        -- the load operation.  The interrupt
                                        -- is enabled per AC(4).  See HD6120
                                        -- GTF instruction.
                                        --

                                        if swCPU = swHD6120 then

                                            if AC(0) = '1' then
                                                acOP <= acopCLACLLCML;
                                            else
                                                acOP <= acopCLACLL;
                                            end if;

                                            if AC(4) = '1' then
                                                ieOP <= ieopSET;
                                                iiOP <= iiopSET;
                                            end if;

                                        --
                                        -- PDP8/E and later: AC is not modified by
                                        -- the instruction. AC(4) is ignored and
                                        -- interrupts are unconditionally
                                        -- re-enabled.  AC(5) sets the UB bit.
                                        -- See PDP/8 GTF instruction.
                                        --

                                        else

                                            if AC(0) = '1' then
                                                acOP <= acopCLLCML;
                                            else
                                                acOP <= acopCLL;
                                            end if;
                                            ieOP <= ieopSET;
                                            iiOP <= iiopSET;
                                            ubOP <= ubopAC5;
                                        end if;

                                        gtfOP <= gtfopAC1;
                                        ibOP  <= ibopAC6to8;
                                        dfOP  <= dfopAC9to11;
                                        fzop  <= fzopCLR;