-------------------------------------------------------------------------------
-- File name : sparc_pck.vhd
-- Title : SparcPck
-- project : SPARC 
-- Library : SPARC_LIB
-- Author(s) : Maxime ROCCA, Jiri Gaisler
-- Purpose : package containing definitions for SPARC environment
-- notes : 
-- 	
-------------------------------------------------------------------------------
-- Modification history :
-------------------------------------------------------------------------------
-- Version No : | Author | Mod. Date : | Changes made :
-------------------------------------------------------------------------------
-- v 1.0        |  MR    | 94-03-04    | first version
--.............................................................................
-- v 1.1        |  MR    | 94-05-03    | 2nd version
-- + OddParityOf function has been modified (output inverted).
-- + procedure IOPscheduling: erroneous specification in issue 4 of the IURT
--   device specification about hardware interlocks for JMPL, CALL and LOAD 
--   double.
-- + modif. hardware trap priority.
--.............................................................................
-- v 1.2        |  MR    | 94-05-27    | 3rd version
-- + define specific timing checker for D & DPAR signals
--.............................................................................
-- v 1.3        |  RC    | 95-12-11    | 4rd version
-- + define RegFile and TrapVector as an inout 
--.............................................................................
-- v 1.4        |  JG    | 96-03-06    | 5rd version
-- + bug fix: correct stored PC and nPC after tapped LD and LDD
-------------------------------------------------------------------------------
-- Copyright MATRA MARCONI SPACE FRANCE
-- Copyright ESA/ESTEC

--  This library is free software; you can redistribute it and/or
--  modify it under the terms of the GNU Library General Public
--  License as published by the Free Software Foundation; either
--  version 2 of the License, or (at your option) any later version.
 
--  This library 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
--  Library General Public License for more details.
 
--  You should have received a copy of the GNU Library General Public
--  License along with this library; if not, write to the Free
--  Software Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA.
 
-------------------------------------------------------------------------------
---------|---------|---------|---------|---------|---------|---------|--------|

library IEEE;
use IEEE.Std_Logic_1164.all;
library MMS;
use MMS.StdRtl.all;
use MMS.StdSim.all;
use MMS.StdIoImp.all;


package SparcPck is


  -- Size of data bus transfer.
  constant BYTE       : natural := 0;
  constant HALFWORD   : natural := 1;
  constant WORDTYPE   : natural := 2;
  constant DOUBLEWORD : natural := 3;

  -- Address Space Identifiers.
  constant USER_INST       : natural :=  8;
  constant USER_DATA       : natural := 10;
  constant SUPERVISOR_INST : natural :=  9;
  constant SUPERVISOR_DATA : natural := 11;

  -- Number of implemented windows
  constant NWINDOWS : natural := 8;
  
  -- Bit numbers for icc  
  constant N_ICC : natural := 3;
  constant Z_ICC : natural := 2;
  constant V_ICC : natural := 1;
  constant C_ICC : natural := 0;
  
  -- Values for the impl & ver fields of the PSR
  constant PSR_IMPL : std_logic_vector(3 downto 0) := "0001";
  constant PSR_VER  : std_logic_vector(3 downto 0) := "0001";
  constant TBR3_DOWNTO_0  : std_logic_vector(3 downto 0) := "0000";
            
  -- Processor states or modes.
  type ModeType is (RESET_MODE, ERROR_MODE, EXECUTE_MODE);

  -- Mnemonics for instructions.
  type SuperInstMnemonic is (  -- including pseudo-instructions
     -- pseudo-instruction mnemonics for modelling purposes
     XXX, ILLEGAL, IOP, NOTHING, ANNULLED,
     
     -- SPARC instruction set
        --- Load/Store Instruction Mnemonics ---
     LD      , LDA     , LDC      , LDCSR   , LDD     ,
     LDDA    , LDDC    , LDDF     , LDF     , LDFSR   ,
     LDSB    , LDSBA   , LDSH     , LDSHA   , LDSTUB  ,
     LDSTUBA , LDUB    , LDUBA    , LDUH    , LDUHA   ,
     ST      , STA     , STB      , STBA    , STC     ,
     STCSR   , I_STD     , STDA     , STDC    , STDCQ   ,
     STDF    , STDFQ   , STF      , STFSR   , STH     ,
     STHA    , SWAP    , SWAPA    ,
        --- Arithmetic/Logical/Shift Instruction Mnemonics ---
     ADD     , ADDcc   , ADDX     , ADDXcc  , I_AND   ,
     ANDcc   , ANDN    , ANDNcc   , MULScc  , I_OR    ,
     ORcc    , ORN     , ORNcc    , SLL     , SRA     ,
     SRL     , SUB     , SUBcc    , SUBX    , SUBXcc  ,
     TADDcc  , TADDccTV, TSUBcc   , TSUBccTV, XNOR    ,
     XNORcc  , I_XOR   , XORcc    ,
        --- Control Transfer Instruction Mnemonics ---
     JMPL    , RESTORE , RETT     , SAVE    , CALL    ,
     BN      , BE      , BLE      , BL      , BLEU    ,
     BCS     , BNEG    , BVS      , BA      , BNE     ,
     BG      , BGE     , BGU      , BCC     , BPOS    ,
     BVC     , CBN     , CB123    , CB12    , CB13    ,
     CB1     , CB23    , CB2      , CB3     , CBA     ,
     CB0     , CB03    , CB02     , CB023   , CB01    ,
     CB013   , CB012   , FBN      , FBNE    , FBLG    ,
     FBUL    , FBL     , FBUG     , FBG     , FBU     ,
     FBA     , FBE     , FBUE     , FBGE    , FBUGE   ,
     FBLE    , FBULE   , FBO      , TN      , TE      ,
     TLE     , TL      , TLEU     , TCS     , TNEG    ,
     TVS     , TA      , TNE      , TG      , TGE     ,
     TGU     , TCC     , TPOS     , TVC     ,
        --- Read/Write Control Register Instruction Mnemonics ---
     RDPSR   , RDTBR   , RDWIM    , RDY     , WRPSR   ,
     WRTBR   , WRWIM   , WRY      ,
        --- Miscellaneous Instruction Mnemonics ---
     SETHI   , UNIMP   , FLUSH    , -- IFLUSH instead of FLUSH in SPARC v.7
     RDASR   , WRASR   , STBAR    , -- SPARC v.8 only
        --- Integer Multiply/Divide Instructions Mnemonics ---
                   --- SPARC Version 8 only ---
     UMUL    , UMULcc  , SMUL     , SMULcc   , UDIV   ,
     UDIVcc  , SDIV    , SDIVcc   ,
        --- Floating-Point Instruction Mnemonics ---
     FiTOs   , FiTOd   , FiTOq    , FsTOi    , FdTOi  ,
     FqTOi   , FsTOd   , FsTOq    , FdTOs    , FdTOq  ,
     FqTOs   , FqTOd   , FMOVs    , FNEGs    , FABSs  ,
     FSQRTs  , FSQRTd  , FSQRTq   , FADDs    , FADDd  ,
     FADDq   , FSUBs   , FSUBd    , FSUBq    , FMULs  ,
     FMULd   , FMULq   ,
     FsMULd  , FdMULq  , -- SPARC v.8 only for FsMULd & FdMULq
     FDIVs   , FDIVd   , FDIVq    , FCMPs    , FCMPd  ,
     FCMPq   , FCMPEs  , FCMPEd   , FCMPEq   ,
        --- Coprocessor Instruction Mnemonics ---
      CPop1  , CPop2    
  );


  -- Pseudo-functions to tell if an instruction mnemonic is an OPcc (IsOPcc)
  -- or a Bicc or a FBfcc or CBccc.
  -- Constants have deferred values.
  type IsOPccType is array(SuperInstMnemonic) of boolean;
  constant IsOPcc : IsOPccType;
  type IsBranchingInstType is array(SuperInstMnemonic) of boolean;
  constant IsBicc  : IsBranchingInstType;
  constant IsFBfcc : IsBranchingInstType;
  constant IsCBccc : IsBranchingInstType;
  
  -- Other pseudo-functions:
  -- IURs1Rs2AreIn(Mnemonic) returns TRUE if Mnemonic has a source register
  -- rs1 or rs2.
  -- FPURsIsIn(Mnemonic) returns TRUE if Mnemonic has a source register
  -- rs1.
  -- IsFPinst(Mnemonic) returns TRUE if Mnemonic is a FP instruction.
  -- IsFPop(Mnemonic) returns TRUE if Mnemonic is a FP operation.
  -- IsFCMP(Mnemonic) returns TRUE if Mnemonic is a FP compare.
  type MnemoTableType is array(SuperInstMnemonic) of boolean;
  constant IURs1Rs2AreIn : MnemoTableType;
  constant FPURs1IsIn    : MnemoTableType;
  constant IsFPinst      : MnemoTableType;
  constant IsFPop        : MnemoTableType;
  constant IsFPopDouble  : MnemoTableType;
  constant IsFPopQuad    : MnemoTableType;
  constant IsFCMP        : MnemoTableType;
  
  -- Other pseudo-functions for LOAD AND STORE instructions
  -- IsLoadDoubleInst(Mnemonic) returns TRUE if Mnemonic is a LOAD instruction
  -- for double words.
  -- IsLoadInst(Mnemonic) returns TRUE if Mnemonic is a LOAD instruction.
  -- IsLoadSingleInst(Mnemonic) returns TRUE if Mnemonic is a LOAD instruction
  -- for "single" words.
  -- IsLoadFP_CPInst(Mnemonic) returns TRUE if Mnemonic is a Floating-Point
  -- or Coprocessor LOAD.
  -- IsStoreInst(Mnemonic) returns TRUE if Mnemonic is a store instruction.
  -- and so on...
  constant IsLoadDoubleInst   : MnemoTableType;
  constant IsLoadInst         : MnemoTableType;
  constant IsLoadSingleInst   : MnemoTableType;
  constant IsLoadFP_CPInst    : MnemoTableType;
  constant IsLoadByteInst     : MnemoTableType;
  constant IsLoadHalfwordInst : MnemoTableType;
  constant IsLoadInstASI      : MnemoTableType;
  constant IsStoreInst        : MnemoTableType;
  constant IsStoreDoubleInst  : MnemoTableType;
  constant IsStoreFP_CPInst   : MnemoTableType;
  constant IsStoreInstASI     : MnemoTableType;
  constant IsStoreSingleInst  : MnemoTableType;
  
  type Instruction is record
     Mnemo       : SuperInstMnemonic; -- mnemonic of an instruction
     asi         : natural; -- address space identifier
     i           : natural; -- i bit
     a           : natural; -- annul bit for branch instructions
     rd          : natural; -- destination register
     rs1         : natural; -- source register 1
     rs2         : natural; -- source register 2
     simm13      : natural; -- 13-bit immediate value
     disp30      : std_logic_vector(29 downto 0); -- displacement for CALL
     disp22      : natural; -- 22-bit displacement for taken branches
                            -- or 22-bit constant for SETHI & UNIMP inst.
     
     Address     : std_logic_vector(31 downto 0); -- instruction address
     NextAddress : std_logic_vector(31 downto 0); -- addr. of the following
                                                  -- instruction
     Annul       : boolean; -- for branching instruction: TRUE if annulled
     BitInstr    : std_logic_vector(31 downto 0); -- 32-bit value of instr.
  end record; -- Instruction
  
  -- RegisterFile: unbounded array of 32-bit words.
  type RegisterFile is array(natural range <>) of std_logic_vector(31 downto 0);
  
  -- Declarations related to trap handling.
  type TrapMnemonic is (
     DETECTED_TRAP,   -- Used to set flag when a trap is detected (except for
                      -- reset traps).
     RESET_TRAP,      -- reset trap mnemo.
     INST_ACCESS,     -- instruction access exception trap
     ILLEGAL_INST,    -- illegal instruction trap
     PRIVILEGED_INST, -- privileged instruction trap
     FP_DISABLED,     -- Floating-Point disabled trap
     CP_DISABLED,     -- Coprocessor disabled trap
     WINDOW_OVERFLOW, -- window overflow trap
     WINDOW_UNDERFLOW, -- window underflow trap
     MEM_ADDR_NOT_ALIGNED, -- memory-address-not-aligned trap
     FP_EXCEPTION,    -- Floating-Point exception trap
     CP_EXCEPTION,    -- Coprocessor exception trap
     DATA_ACCESS_EXCEPTION, -- data access exception trap
     TAG_OVERFLOW,    -- tag overflow trap for TADDccTV & TSUBccTV
     TRAP_INST,       -- trap instruction Ticc
     INTERRUPT_LEVEL, -- interrupting trap with IRL(3:0)
     PROGRAM_FLOW_ERR, -- Program Flow Error (hardware trap).
     NON_RESTART_IMPRECISE, -- Non-restartable, imprecise error.
     RESTART_IMPRECISE -- Restartable, imprecise error
  );
  
  type TrapVectorType is array(TrapMnemonic) of boolean;
  type TrapType is array(TrapMnemonic) of std_logic_vector(7 downto 0);
  constant TrapTypeTable : TrapType := 
  (
    DETECTED_TRAP         => "00000000", -- no trap type here! Dummy constant!
    RESET_TRAP            => "00000000", -- same thing here (Dummy constant).
    INST_ACCESS           => "00000001", 
    ILLEGAL_INST          => "00000010",
    PRIVILEGED_INST       => "00000011",
    FP_DISABLED           => "00000100",
    CP_DISABLED           => "00100100",
    WINDOW_OVERFLOW       => "00000101",
    WINDOW_UNDERFLOW      => "00000110",
    MEM_ADDR_NOT_ALIGNED  => "00000111",
    FP_EXCEPTION          => "00001000",
    CP_EXCEPTION          => "00101000",
    DATA_ACCESS_EXCEPTION => "00001001",
    TAG_OVERFLOW          => "00001010",
    TRAP_INST             => "00000000", -- Dummy constant: trap type is 
                                         -- computed during execution of Ticc.
    INTERRUPT_LEVEL       => "00000000", -- Dummy constant: trap type is
                                         -- determined by concatenating 0001
                                         -- with IRL value: 0001 & IRL(3:0).
    PROGRAM_FLOW_ERR      => "01100110",
    NON_RESTART_IMPRECISE => "01100100",
    RESTART_IMPRECISE     => "01100011"
  );
  
  type TrapModeType is (
     NOTRAP,       -- no trap condition
     SYNCH_TRAP,   -- SYNCHronous trap
     ASYNCH_TRAP   -- ASYNCHronous trap
  );
  

--============== FUNCTIONS DECLARATIONS  ======================================

  
  -----------------------------------------------------------------------------
  -- GetIndex emulates the windowing scheme of the windowed register file by
  -- returning the right index for this register file.
  -- n: the input index (0<n<31)
  -- CWP: Current Window Pointer
  -----------------------------------------------------------------------------
  function GetIndex(n : natural; CWP : std_logic_vector) return natural;
  
  -----------------------------------------------------------------------------
  -- This function "decodes" a 32-bit vector considered as being a SPARC
  -- instruction by returning a record "Instruction" containing all the  
  -- meaningful information needed to execute this instruction.
  -- A must be a 32-bit vector. The function will crash if A'length is less
  -- than 32, and assert an error if greater than 32. Moreover, A should be
  -- defined as A(31:0), i.e MSB with highest index.
  -- Note: SPARC v.8 instructions RDASR, WRASR & STBAR are not decoded by this
  -- function.
  -----------------------------------------------------------------------------
  function Transcribe(A : std_logic_vector) return Instruction;
  
  -----------------------------------------------------------------------------
  -- Evaluates the icc and returns TRUE if the branch should be taken.
  -----------------------------------------------------------------------------
  function iccEvaluation(Mnemonic : SuperInstMnemonic;
                         icc      : std_logic_vector) return boolean;
                         
  -----------------------------------------------------------------------------
  -- Same as iccEvaluation for Ticc instructions.
  -----------------------------------------------------------------------------
  function TiccEval(Mnemonic : SuperInstMnemonic;
                    icc      : std_logic_vector) return boolean;
                         
  -----------------------------------------------------------------------------
  -- Same as above for FPU with fcc.
  -----------------------------------------------------------------------------
  function fccEvaluation(Mnemonic   : SuperInstMnemonic;
                         signal fcc : std_logic_vector) return boolean;

  -----------------------------------------------------------------------------
  -- Returns TRUE if there is a register dependency between rd and InstB 
  -- (i.e one of the source register of InstB is the destination register rd).
  -- Valid for register of the IU (not the FP registers).
  -----------------------------------------------------------------------------
  function IURegDependency(rd    : natural;
                           InstB : Instruction) return boolean;
                           
  -----------------------------------------------------------------------------
  -- Returns TRUE if there is a register dependency between rd and InstB 
  -- (i.e one of the source register of InstB is the destination register rd).
  -- Valid for registers of the FPU (FP registers).
  -- WARNING: THIS FUNCTION IS OBSOLETE and kept here for information.
  -----------------------------------------------------------------------------
--  function FPURegDependency(rd    : natural;
--                            Mnemo : SuperInstMnemonic;
--                            rs1   : natural;
--                            rs2   : natural) return boolean;

  -----------------------------------------------------------------------------
  -- Computes the value of the address for a load, store or load-store 
  -- instruction.
  -----------------------------------------------------------------------------
  function LoadORStoreORSwapAddrCalc(Inst    : Instruction;
                                     CWP     : std_logic_vector;
                                     RegFile : RegisterFile) 
                                        return std_logic_vector;

  -----------------------------------------------------------------------------
  -- Computes the odd parity over a given std_logic_vector
  -----------------------------------------------------------------------------
  function OddParityOf(Vec : std_logic_vector) return std_logic;

--============== PROCEDURES DECLARATIONS ======================================

  -----------------------------------------------------------------------------
  -- This procedure detects traps (for asynchronous traps) and does the opera-
  -- -tions to be performed when a trap case is present.
  -- All std_logic_vector parameters must be 32 bits long.
  -- Interrupting traps (asynchronous traps) are also taken care of.
  -----------------------------------------------------------------------------
  procedure TrapHandler(signal EX   : Instruction;
                        signal WR   : Instruction;
                               WR1  : Instruction;
                               WR2  : Instruction;
                        pIRLvar     : natural;
                        IRLvar      : natural;
                        TBR         : inout std_logic_vector;
                        PSR         : inout std_logic_vector;
                        TrapVector  : inout TrapVectorType;
                        Mode        : inout ModeType;
                        TrapMode    : out TrapModeType;
                        pPrevAddr   : inout std_logic_vector;
                        PrevAddr    : inout std_logic_vector;
                        CurrentAddr : inout std_logic_vector;
 --                       RegFile     : out RegisterFile); --gd 2208
 -- we dont want to erase the old value
                        RegFile     : inout RegisterFile);
  
  -----------------------------------------------------------------------------
  -- This procedure does the dispatching for instruction execution. Trap flags 
  -- are set when traps are detected for each "family" of instructions.
  -- ResultOpcc, iccTemp, YTemp are parameters for "anticipated" execution of
  -- certain instructions (OPcc instructions).
  -- ResultOpcc, Y, YTemp, PSR, TBR, WIM lengths must be 32 bits long.
  -- iccTemp length must be 4 bits long.
  -----------------------------------------------------------------------------
  procedure ExecutionBody(signal FP_N : std_logic;
                          signal IFT_N: std_logic;
                          signal EX   : Instruction;
                          ResultOpcc  : std_logic_vector;
                          YTemp       : std_logic_vector;
                          iccTemp     : inout std_logic_vector;
                          Y           : inout std_logic_vector;
                          PSR         : inout std_logic_vector;
                          TBR         : inout std_logic_vector;
                          WIM         : inout std_logic_vector;
                          RegFile     : inout RegisterFile;
                          Mode        : inout ModeType;
                          TrapVector  : inout TrapVectorType);
  
  -----------------------------------------------------------------------------
  -- Execution of LOAD instructions. The procedure only detects trap conditions.
  -- The address of the data to load is computed earlier so that the data can
  -- be fetched in time on the bus.
  -----------------------------------------------------------------------------
  procedure LoadInstruction(signal FP_N : std_logic;
                            EX          : Instruction;
                            PSR         : std_logic_vector;
                            RegFile     : RegisterFile;
                            TrapVector  : inout TrapVectorType);
                            
  -----------------------------------------------------------------------------
  -- Execute the store instructions. Detects trap conditions and set the trap
  -- vector accordingly.
  -----------------------------------------------------------------------------
  procedure StoreInstruction(signal FP_N : std_logic;
                             EX          : Instruction;
                             PSR         : std_logic_vector;
                             RegFile     : RegisterFile;
                             TrapVector  : inout TrapVectorType);
                             
  -----------------------------------------------------------------------------
  -- This procedure performs all the logical operations. OPcc being executed by
  -- "anticipation", their results are used (with the parameters ResultOPcc and
  -- iccTemp) to assign the register file and icc of the PSR.
  -----------------------------------------------------------------------------
  procedure LogicalInstruction(EX         : Instruction;
                               CWP        : std_logic_vector;
                               ResultOPcc : std_logic_vector;
                               iccTemp    : std_logic_vector;
                               RegFile    : inout RegisterFile;
                               icc        : out std_logic_vector);
                               
  -----------------------------------------------------------------------------
  -- Additions and substractions are performed here. Same as above for OPcc and
  -- parameters.
  -----------------------------------------------------------------------------
  procedure AddSubInstruction(EX         : Instruction;
                              CWP        : std_logic_vector;
                              ResultOPcc : std_logic_vector;
                              iccTemp    : std_logic_vector;
                              RegFile    : inout RegisterFile;
                              icc        : inout std_logic_vector);
  
                            
  -----------------------------------------------------------------------------
  -- Logical and arithmetic shifts. Integer conditions codes are not affected 
  -- by these instructions.
  -----------------------------------------------------------------------------
  procedure ShiftInstruction(EX         : Instruction;
                             CWP        : std_logic_vector;
                             RegFile    : inout RegisterFile);
                             
  -----------------------------------------------------------------------------
  -- Same as AddSubInstruction but with tags. There can be trap conditions.
  -----------------------------------------------------------------------------
  procedure TaggedAddSubbInst(EX         : Instruction;
                              CWP        : std_logic_vector;
                              ResultOPcc : std_logic_vector;
                              iccTemp    : std_logic_vector;
                              icc        : out std_logic_vector;
                              RegFile    : inout RegisterFile;
--                              RegFile    : out RegisterFile; --gd 2208
                              TrapVector : inout TrapVectorType);
                              
  -----------------------------------------------------------------------------
  -- This is an OPcc instruction (affecting the Integer Condition Codes); so it
  -- is executed by anticipation in ExecuteOPcc. Y, icc and RegFile are assigned
  -- with their right value YTemp, iccTemp, ResultOPcc computed in ExecuteOPcc.
  -----------------------------------------------------------------------------
  procedure MultiplyStepInst(EX         : Instruction;
                             CWP        : std_logic_vector;
                             ResultOPcc : std_logic_vector;
                             iccTemp    : std_logic_vector;
                             YTemp      : std_logic_vector;
                             Y          : out std_logic_vector;
                             icc        : out std_logic_vector;
                             RegFile    : inout RegisterFile); --gd 2208
--                             RegFile    : out RegisterFile);
  
  -----------------------------------------------------------------------------
  -- Execution of SAVE/RESTORE instructions. 
  -- Note that the destination register of these instructions is in the NEW
  -- window whereas the source registers come from the OLD window.
  -----------------------------------------------------------------------------
  procedure SaveRestoreInst(EX         : Instruction;
                            WIM        : std_logic_vector;
                            CWP        : inout std_logic_vector;
                            RegFile    : inout RegisterFile;
                            TrapVector : inout TrapVectorType);
                            
  -----------------------------------------------------------------------------
  -- Execution of the instr. RETT, leaving aside the branching address calcula-
  -- -tion which is performed by "anticipation" in ID stage.
  -----------------------------------------------------------------------------
  procedure RettInstruction(EX         : Instruction;
                            RegFile    : RegisterFile;
                            WIM        : std_logic_vector;
                            PSR        : inout std_logic_vector;
                            Mode       : inout ModeType;
                            tt         : out std_logic_vector;
                            TrapVector : inout TrapVectorType);
                            
  -----------------------------------------------------------------------------
  -- Execution of the instr. JMPL, leaving aside the branching address calcula-
  -- -tion which is performed by "anticipation" in ID stage.
  -----------------------------------------------------------------------------
  procedure JmplInstruction(EX         : Instruction;
                            CWP        : std_logic_vector;
                            RegFile    : inout RegisterFile;
                            TrapVector : inout TrapVectorType);
                            
  -----------------------------------------------------------------------------
  -- Branching address calculation for JMPL/RETT instructions.
  -- Done by "anticipation" in ID stage.
  -----------------------------------------------------------------------------
  procedure JmplRettAddrCalc(ID          : Instruction;
                             CWP         : std_logic_vector;
                             RegFile     : RegisterFile;
                             CurrentAddr : out std_logic_vector);
                            
  -----------------------------------------------------------------------------
  -- Instructions reading the state registers are executed in this procedure.
  -- If some trap conditions are encountered, the trap vector is assigned with 
  -- the correct values to tell the trap handler what to do.
  -----------------------------------------------------------------------------
  procedure ReadStateRegInst(EX         : Instruction;
                             PSR        : std_logic_vector;
                             TBR        : std_logic_vector;
                             WIM        : std_logic_vector;
                             Y          : std_logic_vector;
                             TrapVector : inout TrapVectorType;
                             RegFile    : inout RegisterFile);
 --                            RegFile    : out RegisterFile);
                             
  -----------------------------------------------------------------------------
  -- Instructions writing the state registers are executed in this procedure.
  -- Same as above for trap detection.
  -----------------------------------------------------------------------------
  procedure WriteStateRegInst(EX         : Instruction;
                              RegFile    : RegisterFile;
                              PSR        : inout std_logic_vector; 
                              iccTemp    : out std_logic_vector;
                              TBR        : inout std_logic_vector; 
--                              TBR        : out std_logic_vector;--gd 
                              WIM        : inout std_logic_vector; 
--                              WIM        : out std_logic_vector;--gd 
                              Y          : inout std_logic_vector; 
--                              Y          : out std_logic_vector;--gd 
                              TrapVector : inout TrapVectorType);
                              
  -----------------------------------------------------------------------------
  -- This procedure detects trap conditions for LDSTUBA and SWAPA instructions.
  -- Address calculation is not performed for sequencing reasons.
  -----------------------------------------------------------------------------
  procedure LoadStoreSwapInstruction(EX         : Instruction;
                                     S          : std_logic;
                                     CWP        : std_logic_vector;
                                     RegFile    : RegisterFile;
                                     TrapVector : inout TrapVectorType);
                                 
  -----------------------------------------------------------------------------
  -- Execution of trap instructions. Computation of the trap number when
  -- the trap is taken and assignment of the tt field of the TBR with the com-
  -- -puted value.
  -----------------------------------------------------------------------------
  procedure TiccInstruction(EX         : Instruction;
                            CWP        : std_logic_vector;
                            icc        : std_logic_vector;
                            RegFile    : RegisterFile;
                            tt         : out std_logic_vector;
                            TrapVector : inout TrapVectorType);
                            
  -----------------------------------------------------------------------------
  -- This procedure executes OPcc (operations affecting the Integer Condition
  -- Codes) "in advance" ("anticipated" execution).
  -- Results are stored in temporary data objects ResultOPcc, YTemp and 
  -- iccTemp.
  -- These temp. data objects are used to assign the register file and icc of
  -- the PSR (ex.: for OPcc = ADDcc, execution is performed in the procedure
  -- ExecuteOPcc. The register file and icc are assigned in the procedure
  -- AddSubInstruction).
  -----------------------------------------------------------------------------
  procedure ExecuteOPcc(ID         : Instruction;
                        RegFile    : RegisterFile;
                        CWP        : std_logic_vector;
                        icc        : std_logic_vector;
                        Y          : std_logic_vector;
                        ResultOPcc : out std_logic_vector;
                        iccTemp    : out std_logic_vector;
                        YTemp      : out std_logic_vector);
                        
  -----------------------------------------------------------------------------
  -- "Anticipated" execution of Bicc, to calculate the branching address in 
  -- time. No action is taken in the execution body procedure for these instr.
  ----------------------------------------------------------------------------
  procedure ExecuteBicc(iccTemp     : std_logic_vector;
                        icc         : std_logic_vector;
                        nID         : inout Instruction;
                        CurrentAddr : inout std_logic_vector;
                        TakenBr     : out boolean);
                        
  -----------------------------------------------------------------------------
  -- Same as above for Floating-point branch.
  -----------------------------------------------------------------------------
  procedure ExecuteFBfcc(signal fcc  : std_logic_vector;
                         nID         : inout Instruction;
                         CurrentAddr : inout std_logic_vector;
                         TakenBr     : out boolean);
                        
  -----------------------------------------------------------------------------
  -- Puts nID in the instruction buffer (FIFO)
  -----------------------------------------------------------------------------
  procedure PutInBufferQueue(nID         : Instruction;
                             Buf1IsValid : inout boolean;
                             InstBuffer1 : inout Instruction;
                             Buf2IsValid : inout boolean;
                             InstBuffer2 : inout Instruction);
                             
  -----------------------------------------------------------------------------
  -- Sets flag IOPcase to TRUE if an IOP is to be scheduled.
  -----------------------------------------------------------------------------
  procedure IOPscheduling(InstBuffer1 : Instruction;
                          nID         : Instruction;
                          signal ID   : Instruction;
                          signal EX   : Instruction;
                          signal WR   : Instruction;
                          IOPcase     : out boolean);

  -----------------------------------------------------------------------------
  -- Gets an instruction from the instruction buffer (FIFO) and puts it 
  -- in nIDTemp.
  -----------------------------------------------------------------------------
  procedure GetFromBufferQueue(Buf1IsValid : inout boolean;
                               InstBuffer1 : inout Instruction;
                               Buf2IsValid : inout boolean;
                               InstBuffer2 : inout Instruction;
                               nIDTemp     : out Instruction);
                              
  -----------------------------------------------------------------------------
  -- Fetch data on data bus when WR is load instruction and the register rd of
  -- instruction WR is not 0.
  -----------------------------------------------------------------------------
  procedure DataFetchForLoadAndLdstInst(
                          CurrentAddr     : std_logic_vector;
                          signal D        : std_logic_vector;
                          CWP             : std_logic_vector;
                          signal WR       : Instruction;
                          WR1             : Instruction;
                          RegFile         : inout RegisterFile;
                          SwapData        : out std_logic_vector);

  -----------------------------------------------------------------------------
  -- This procedure fetches the data that appears on the bus when a cache miss
  -- case is encountered and serviced. It is essentially used for load and 
  -- load-store instructions.
  -----------------------------------------------------------------------------
  procedure DataFetchWhenCacheMiss(Addr     : std_logic_vector;
                                   signal D : std_logic_vector;
                                   CWP      : std_logic_vector;
                                   WR1      : Instruction;
                                   WR2      : Instruction;
                                   RegFile  : inout RegisterFile);

  -----------------------------------------------------------------------------
  -- Procedure to perform setup and hold time violation checking for the 
  -- data bus and its parity bit.
  -----------------------------------------------------------------------------
  procedure DbusSetupHoldCheck (signal Data    : std_logic_vector;  
                                signal CLK     : std_ulogic;
                                signal XHOLD_N : std_ulogic;
                                constant SETUP, HOLD : time := 0 ns;
                                constant PATH  : string := "";
                                signal DelayedData : std_logic_vector;
                                signal EN_CHECKING : boolean);

  procedure DbusSetupHoldCheck (signal Data    : std_ulogic;  
                                signal CLK     : std_ulogic;
                                signal XHOLD_N : std_ulogic;
                                constant SETUP, HOLD : time := 0 ns;
                                constant PATH  : string := "";
                                signal DelayedData : std_ulogic;
                                signal EN_CHECKING : boolean);

end SparcPck; -- package


-------------------------------------------------------------------------------
-------------------------------------------------------------------------------

package body SparcPck is
  
  -------------------------------------
  constant IsOPcc : IsOPccType :=(
       ADDcc    => TRUE,
       ANDcc    => TRUE,
       ORcc     => TRUE,
       XORcc    => TRUE,
       SUBcc    => TRUE,
       ANDNcc   => TRUE,
       ORNcc    => TRUE,
       XNORcc   => TRUE,
       ADDXcc   => TRUE,
       UMULcc   => TRUE, -- SPARC v.8
       SMULcc   => TRUE, -- SPARC v.8
       SUBXcc   => TRUE,
       UDIVcc   => TRUE, -- SPARC v.8
       SDIVcc   => TRUE, -- SPARC v.8
       TADDcc   => TRUE,
       TSUBcc   => TRUE,
       TADDccTV => TRUE,
       TSUBccTV => TRUE,
       MULScc   => TRUE,
       others => FALSE
  );
  
  -------------------------------------
  constant IsBicc : IsBranchingInstType :=(
       BN   => TRUE,
       BE   => TRUE,
       BLE  => TRUE,
       BL   => TRUE,
       BLEU => TRUE,
       BCS  => TRUE,
       BNEG => TRUE,
       BVS  => TRUE,
       BA   => TRUE,
       BNE  => TRUE,
       BG   => TRUE,
       BGE  => TRUE,
       BGU  => TRUE,
       BCC  => TRUE,
       BPOS => TRUE,
       BVC  => TRUE,
       others => FALSE
  );
  
  -------------------------------------
  constant IsFBfcc : IsBranchingInstType :=(
       FBN   => TRUE,
       FBNE  => TRUE,
       FBLG  => TRUE,
       FBUL  => TRUE,
       FBL   => TRUE,
       FBUG  => TRUE,
       FBG   => TRUE,
       FBU   => TRUE,
       FBA   => TRUE,
       FBE   => TRUE,
       FBUE  => TRUE,
       FBGE  => TRUE,
       FBUGE => TRUE,
       FBLE  => TRUE,
       FBULE => TRUE,
       FBO   => TRUE,
       others => FALSE
  );
  -------------------------------------
  constant IsCBccc : IsBranchingInstType :=(
       CBN   => TRUE,
       CB123 => TRUE,
       CB12  => TRUE,
       CB13  => TRUE,
       CB1   => TRUE,
       CB23  => TRUE,
       CB2   => TRUE,
       CB3   => TRUE,
       CBA   => TRUE,
       CB0   => TRUE,
       CB03  => TRUE,
       CB02  => TRUE,
       CB023 => TRUE,
       CB01  => TRUE,
       CB013 => TRUE,
       CB012 => TRUE,
       others => FALSE
  );
  
  -------------------------------------
  constant IURs1Rs2AreIn : MnemoTableType := (
     LD      => TRUE, LDA   => TRUE, LDC   => TRUE, LDCSR => TRUE,
     LDD     => TRUE,
     LDDA    => TRUE, LDDC  => TRUE, LDDF  => TRUE, LDF   => TRUE,
     LDFSR   => TRUE,
     LDSB    => TRUE, LDSBA => TRUE, LDSH  => TRUE, LDSHA => TRUE,
     LDSTUB  => TRUE,
     LDSTUBA => TRUE, LDUB  => TRUE, LDUBA => TRUE, LDUH  => TRUE,
     LDUHA   => TRUE,
     ST      => TRUE, STA   => TRUE, STB   => TRUE, STBA  => TRUE,
     STC     => TRUE,
     STCSR   => TRUE, I_STD   => TRUE, STDA  => TRUE, STDC  => TRUE,
     STDCQ   => TRUE,
     STDF    => TRUE, STDFQ => TRUE, STF   => TRUE, STFSR => TRUE,
     STH     => TRUE,
     STHA    => TRUE, SWAP  => TRUE, SWAPA => TRUE,
        --- Arithmetic/Logical/Shift Instruction Mnemonics ---
     ADD    => TRUE, ADDcc    => TRUE, ADDX   => TRUE, ADDXcc   => TRUE,
     I_AND  => TRUE,
     ANDcc  => TRUE, ANDN     => TRUE, ANDNcc => TRUE, MULScc   => TRUE,
     I_OR   => TRUE,
     ORcc   => TRUE, ORN      => TRUE, ORNcc  => TRUE, SLL      => TRUE,
     SRA    => TRUE,
     SRL    => TRUE, SUB      => TRUE, SUBcc  => TRUE, SUBX     => TRUE,
     SUBXcc => TRUE,
     TADDcc => TRUE, TADDccTV => TRUE, TSUBcc => TRUE, TSUBccTV => TRUE,
     XNOR   => TRUE,
     XNORcc => TRUE, I_XOR    => TRUE, XORcc  => TRUE,
        --- Control Transfer Instruction Mnemonics ---
     JMPL => TRUE, RESTORE => TRUE, RETT => TRUE, SAVE => TRUE,
     TN   => TRUE, TE      => TRUE,
     TLE  => TRUE, TL      => TRUE, TLEU => TRUE, TCS  => TRUE, TNEG => TRUE,
     TVS  => TRUE, TA      => TRUE, TNE  => TRUE, TG   => TRUE, TGE  => TRUE,
     TGU  => TRUE, TCC     => TRUE, TPOS => TRUE, TVC  => TRUE,
        --- Write Control Register Instruction Mnemonics ---
     WRPSR => TRUE, WRTBR => TRUE, WRWIM => TRUE, WRY => TRUE,
        --- Miscellaneous Instruction Mnemonics ---
     FLUSH => TRUE, -- IFLUSH instead of FLUSH in SPARC v.7
     RDASR => TRUE, WRASR => TRUE, -- SPARC v.8 only
        --- Integer Multiply/Divide Instructions Mnemonics ---
                   --- SPARC Version 8 only ---
     UMUL   => TRUE, UMULcc => TRUE, SMUL   => TRUE, SMULcc => TRUE,
     UDIV   => TRUE,
     UDIVcc => TRUE, SDIV   => TRUE, SDIVcc => TRUE,
       
     others => FALSE
  );

  -------------------------------------
  constant FPURs1IsIn : MnemoTableType := (
    FADDs  => TRUE, FADDd  => TRUE, FADDq  => TRUE, FSUBs  => TRUE,
    FSUBd  => TRUE, FSUBq  => TRUE, FMULs  => TRUE, FMULd  => TRUE, 
    FMULq  => TRUE,
    FsMULd => TRUE, FdMULq => TRUE, -- SPARC v.8 only for FsMULd & FdMULq
    FDIVs  => TRUE, FDIVd  => TRUE, FDIVq  => TRUE, FCMPs  => TRUE,
    FCMPd  => TRUE, FCMPq  => TRUE, FCMPEs => TRUE, FCMPEd => TRUE, 
    FCMPEq => TRUE,
    others => FALSE
  );

  -------------------------------------
  constant IsLoadInst : MnemoTableType := (
     LD    => TRUE, LDD   => TRUE, LDSB  => TRUE, LDUB  => TRUE,
     LDSH  => TRUE, LDUH  => TRUE, LDA   => TRUE, LDDA  => TRUE,
     LDSBA => TRUE, LDUBA => TRUE, LDSHA => TRUE, LDUHA => TRUE,
     LDF   => TRUE, LDDF  => TRUE, LDFSR => TRUE, LDC   => TRUE,
     LDDC  => TRUE, LDCSR => TRUE,
     others  => FALSE
  );
  
  -------------------------------------
  constant IsLoadDoubleInst : MnemoTableType := (
     LDD   => TRUE, LDDA  => TRUE,
     LDDF  => TRUE, LDDC  => TRUE, 
     others  => FALSE
  );
    
  -------------------------------------
  constant IsLoadSingleInst : MnemoTableType := (
     LD    => TRUE, LDSB  => TRUE, LDUB  => TRUE, LDSH  => TRUE,
     LDUH  => TRUE, LDA   => TRUE, LDSBA => TRUE, LDUBA => TRUE,
     LDSHA => TRUE, LDUHA => TRUE, LDF   => TRUE, LDFSR => TRUE, 
     LDC   => TRUE, LDCSR => TRUE,
     others  => FALSE
  );
  
  -------------------------------------
  constant IsLoadFP_CPInst : MnemoTableType := (
     LDF   => TRUE, LDDF  => TRUE, LDFSR => TRUE, LDC   => TRUE,
     LDDC  => TRUE, LDCSR => TRUE,
     others  => FALSE
  );
  
  -------------------------------------
  constant IsLoadByteInst : MnemoTableType := (
     LDSB  => TRUE, LDUB  => TRUE, LDSBA => TRUE, LDUBA => TRUE,
     others  => FALSE
  );
  
  -------------------------------------
  constant IsLoadHalfwordInst : MnemoTableType := (
     LDSH  => TRUE, LDUH  => TRUE, LDSHA => TRUE, LDUHA => TRUE,
     others  => FALSE
  );
  
  -------------------------------------
  constant IsLoadInstASI : MnemoTableType := (
     LDA   => TRUE, LDDA  => TRUE, LDSBA => TRUE, LDUBA => TRUE,
     LDSHA => TRUE, LDUHA => TRUE,
     others  => FALSE
  );

  -------------------------------------
  constant IsStoreInst : MnemoTableType := (
     ST    => TRUE, I_STD   => TRUE, STH  => TRUE, STB  => TRUE, STA   => TRUE,
     STDA  => TRUE, STHA  => TRUE, STBA => TRUE, STF  => TRUE, STDF  => TRUE,
     STFSR => TRUE, STDFQ => TRUE, STC  => TRUE, STDC => TRUE, STCSR => TRUE,
     STDCQ => TRUE,
     others => FALSE
  );
  
  -------------------------------------  
  constant IsStoreFP_CPInst : MnemoTableType := (
    STF  => TRUE, STDF  => TRUE, STFSR => TRUE, STDFQ => TRUE, STC  => TRUE,
    STDC => TRUE, STCSR => TRUE, STDCQ => TRUE,
    others => FALSE
  );
  
  -------------------------------------  
  constant IsStoreDoubleInst : MnemoTableType := (
    I_STD   => TRUE, STDA => TRUE, STDF => TRUE, STDFQ => TRUE, STDC => TRUE,
    STDCQ => TRUE,
    others => FALSE
  );
  
  -------------------------------------  
  constant IsStoreInstASI : MnemoTableType := (
    STA => TRUE, STDA => TRUE, STBA => TRUE, STHA => TRUE,
    others => FALSE
  );
  
  -------------------------------------  
  constant IsStoreSingleInst : MnemoTableType := (
    ST   => TRUE, STH  => TRUE, STB   => TRUE, STA  => TRUE, STBA  => TRUE,
    STHA => TRUE, STF  => TRUE, STFSR => TRUE, STC  => TRUE, STCSR => TRUE,
    others => FALSE
  );
  
  -------------------------------------  
  constant IsFPinst : MnemoTableType := (
    LDDF => TRUE, LDF => TRUE, LDFSR => TRUE, 
    STDF => TRUE, STF => TRUE, STFSR => TRUE,
    STDFQ => TRUE,
    FBN   => TRUE, FBNE => TRUE, FBLG  => TRUE, FBUL => TRUE,
    FBL   => TRUE, FBUG => TRUE, FBG   => TRUE, FBU  => TRUE,
    FBA   => TRUE, FBE  => TRUE, FBUE  => TRUE, FBGE => TRUE,
    FBUGE => TRUE, FBLE => TRUE, FBULE => TRUE, FBO  => TRUE,
    FiTOs  => TRUE, FiTOd  => TRUE, FiTOq  => TRUE, FsTOi  => TRUE,
    FdTOi  => TRUE, FqTOi  => TRUE, FsTOd  => TRUE, FsTOq  => TRUE,
    FdTOs  => TRUE, FdTOq  => TRUE, FqTOs  => TRUE, FqTOd  => TRUE,
    FMOVs  => TRUE, FNEGs  => TRUE, FABSs  => TRUE, FSQRTs => TRUE, 
    FSQRTd => TRUE, FSQRTq => TRUE, FADDs  => TRUE, FADDd  => TRUE,
    FADDq  => TRUE, FSUBs  => TRUE, FSUBd  => TRUE, FSUBq  => TRUE,
    FMULs  => TRUE, FMULd  => TRUE, FMULq  => TRUE,
    FsMULd => TRUE, FdMULq => TRUE, -- SPARC v.8 only for FsMULd & FdMULq
    FDIVs  => TRUE, FDIVd  => TRUE, FDIVq  => TRUE, FCMPs  => TRUE,
    FCMPd  => TRUE, FCMPq  => TRUE, FCMPEs => TRUE, FCMPEd => TRUE, 
    FCMPEq => TRUE,
    others => FALSE
  );
  
  -------------------------------------
  constant IsFPop : MnemoTableType := (
    FiTOs  => TRUE, FiTOd  => TRUE, FiTOq  => TRUE, FsTOi  => TRUE,
    FdTOi  => TRUE, FqTOi  => TRUE, FsTOd  => TRUE, FsTOq  => TRUE,
    FdTOs  => TRUE, FdTOq  => TRUE, FqTOs  => TRUE, FqTOd  => TRUE,
    FMOVs  => TRUE, FNEGs  => TRUE, FABSs  => TRUE, FSQRTs => TRUE, 
    FSQRTd => TRUE, FSQRTq => TRUE, FADDs  => TRUE, FADDd  => TRUE,
    FADDq  => TRUE, FSUBs  => TRUE, FSUBd  => TRUE, FSUBq  => TRUE,
    FMULs  => TRUE, FMULd  => TRUE, FMULq  => TRUE,
    FsMULd => TRUE, FdMULq => TRUE, -- SPARC v.8 only for FsMULd & FdMULq
    FDIVs  => TRUE, FDIVd  => TRUE, FDIVq  => TRUE, FCMPs  => TRUE,
    FCMPd  => TRUE, FCMPq  => TRUE, FCMPEs => TRUE, FCMPEd => TRUE, 
    FCMPEq => TRUE,
    others => FALSE
  );

  -------------------------------------
  constant IsFPopDouble : MnemoTableType := (
    FdTOi  => TRUE, FdTOs  => TRUE, FdTOq  => TRUE, FSQRTd => TRUE,
    FADDd  => TRUE, FSUBd  => TRUE, FMULd  => TRUE, 
    FdMULq => TRUE, -- SPARC v.8 only for FsMULd & FdMULq
    FDIVd  => TRUE, FCMPd  => TRUE, FCMPEd => TRUE, 
    others => FALSE
  );

  -------------------------------------
  constant IsFPopQuad : MnemoTableType := (
    FqTOi  => TRUE, FqTOs  => TRUE, FqTOd  => TRUE, FSQRTq => TRUE,
    FADDq  => TRUE, FSUBq  => TRUE, FMULq  => TRUE, FDIVq  => TRUE,
    FCMPq  => TRUE, FCMPEq => TRUE,
    others => FALSE
  );

  -------------------------------------
  constant IsFCMP : MnemoTableType := (
    FCMPs  => TRUE, FCMPd  => TRUE, FCMPq => TRUE,
    FCMPEs => TRUE, FCMPEd => TRUE, FCMPEq => TRUE,
    others => FALSE
  );  
  
  -------------------------------------
  function GetIndex(n : natural; CWP : std_logic_vector) return natural is
    variable Temp, CWPvar : natural;
  begin
    assert (n >= 0 and n < 32) report "(GetIndex): wrong value for n!"
                               severity error;
                  
    if (n >= 0 and n <= 7) then return n; -- global registers.
    end if;
    
    CWPvar := ToNatural(CWP);
    assert CWPvar < NWINDOWS report "(GetIndex): wrong value for CWP!"
                             severity error;
                  
    Temp := (n - 8 + CWPvar*16) mod (16*NWINDOWS) + 8;
    return Temp;
  end GetIndex; -- function
  
  -------------------------------------
  function Transcribe(A : std_logic_vector) return Instruction is
    constant L : natural := A'length;
    alias op     : std_logic_vector(1 downto 0) is A(31 downto 30);
    alias op2    : std_logic_vector(2 downto 0) is A(24 downto 22);
    alias op3    : std_logic_vector(5 downto 0) is A(24 downto 19);
    alias opf    : std_logic_vector(8 downto 0) is A(13 downto 5);
    alias cond   : std_logic_vector(3 downto 0) is A(28 downto 25);
    alias asi    : std_logic_vector(7 downto 0) is A(12 downto 5);
    alias i      : std_logic is A(13);
    alias a_bit  : std_logic is A(29);
    alias rd     : std_logic_vector(4 downto 0) is A(29 downto 25);
    alias rs1    : std_logic_vector(4 downto 0) is A(18 downto 14);
    alias rs2    : std_logic_vector(4 downto 0) is A( 4 downto 0);
    alias simm13 : std_logic_vector(12 downto 0) is A(12 downto 0);
    alias disp30 : std_logic_vector(29 downto 0) is A(29 downto 0);
    alias disp22 : std_logic_vector(21 downto 0) is A(21 downto 0);
    variable Result : Instruction;
  begin
    assert L = 32 report "(Transcribe): invalid vector length!"
                  severity error;
                  
    if VecUnknown(A) then
      Result.Mnemo := XXX;
      return Result; -- exit function here if unknown bits in A
    end if;
   
    -- For almost all instructions, these 5 fields are relevant: so
    -- they are assigned for all instructions.
    Result.BitInstr := A;
    Result.rd  := ToNatural(rd);
    Result.rs1 := ToNatural(rs1);
    Result.rs2 := ToNatural(rs2);
    Result.simm13 := ToNatural(simm13);
    if i = '0' then
      Result.i := 0; -- Result.i is a natural.
    else
      Result.i := 1;
    end if;
    
    case op is   -- 1st level
    
      when "00" =>  ---------- OP testing ---------------
      
        Result.disp22 := ToNatural(disp22); -- Common statement for op="00".
        Result.Annul := FALSE; -- explicit assignment to FALSE.
        
        case op2 is  -- 2nd level
          when "100" => -------------- OP + OP2 testing --------------
            Result.Mnemo := SETHI;
          when "010" => -------------- OP + OP2 testing --------------
            case cond is  -- 3rd level
              when "0000" => Result.Mnemo := BN;
              when "0001" => Result.Mnemo := BE;
              when "0010" => Result.Mnemo := BLE;
              when "0011" => Result.Mnemo := BL;
              when "0100" => Result.Mnemo := BLEU;
              when "0101" => Result.Mnemo := BCS;
              when "0110" => Result.Mnemo := BNEG;
              when "0111" => Result.Mnemo := BVS;
              when "1000" => Result.Mnemo := BA;
              when "1001" => Result.Mnemo := BNE;
              when "1010" => Result.Mnemo := BG;
              when "1011" => Result.Mnemo := BGE;
              when "1100" => Result.Mnemo := BGU;
              when "1101" => Result.Mnemo := BCC;
              when "1110" => Result.Mnemo := BPOS;
              when "1111" => Result.Mnemo := BVC;
              when others => NULL;
            end case; -- cond
            if a_bit = '0' then 
              Result.a := 0; -- Result.a is a natural.
            else
              Result.a := 1;
            end if;
            
          when "110" => -------------- OP + OP2 testing --------------
            case cond is  -- 3rd level
              when "0000" => Result.Mnemo := FBN;
              when "0001" => Result.Mnemo := FBNE;
              when "0010" => Result.Mnemo := FBLG;
              when "0011" => Result.Mnemo := FBUL;
              when "0100" => Result.Mnemo := FBL;
              when "0101" => Result.Mnemo := FBUG;
              when "0110" => Result.Mnemo := FBG;
              when "0111" => Result.Mnemo := FBU;
              when "1000" => Result.Mnemo := FBA;
              when "1001" => Result.Mnemo := FBE;
              when "1010" => Result.Mnemo := FBUE;
              when "1011" => Result.Mnemo := FBGE;
              when "1100" => Result.Mnemo := FBUGE;
              when "1101" => Result.Mnemo := FBLE;
              when "1110" => Result.Mnemo := FBULE;
              when "1111" => Result.Mnemo := FBO;
              when others => NULL;
            end case; -- cond            
            if a_bit = '0' then
              Result.a := 0; -- Result.a is a natural.
            else
              Result.a := 1;
            end if;
            
          when "111" => -------------- OP + OP2 testing --------------
            case cond is  -- 3rd level
              when "0000" => Result.Mnemo := CBN;
              when "0001" => Result.Mnemo := CB123;
              when "0010" => Result.Mnemo := CB12;
              when "0011" => Result.Mnemo := CB13;
              when "0100" => Result.Mnemo := CB1;
              when "0101" => Result.Mnemo := CB23;
              when "0110" => Result.Mnemo := CB2;
              when "0111" => Result.Mnemo := CB3;
              when "1000" => Result.Mnemo := CBA;
              when "1001" => Result.Mnemo := CB0;
              when "1010" => Result.Mnemo := CB03;
              when "1011" => Result.Mnemo := CB02;
              when "1100" => Result.Mnemo := CB023;
              when "1101" => Result.Mnemo := CB01;
              when "1110" => Result.Mnemo := CB013;
              when "1111" => Result.Mnemo := CB012;
              when others => NULL;
            end case; -- cond
            if a_bit = '0' then
              Result.a := 0; -- Result.a is a natural.
            else
              Result.a := 1;
            end if;
            
          when "000" => -------------- OP + OP2 testing --------------
            Result.Mnemo  := UNIMP;
          when others =>
            Result.Mnemo := ILLEGAL; -- Unknown and illegal instruction
        end case; -- op2
        
      when "11" => -------------- OP testing --------------
      
        Result.asi := ToNatural(asi);
        
        case op3 is  -- 2nd level: OP + OP3 testing -------
          when "000000" => Result.Mnemo := LD;
          when "000001" => Result.Mnemo := LDUB;
          when "000010" => Result.Mnemo := LDUH;
          when "000011" => Result.Mnemo := LDD;
          when "000100" => Result.Mnemo := ST;
          when "000101" => Result.Mnemo := STB;
          when "000110" => Result.Mnemo := STH;
          when "000111" => Result.Mnemo := I_STD;
          when "001001" => Result.Mnemo := LDSB;
          when "001010" => Result.Mnemo := LDSH;
          when "001101" => Result.Mnemo := LDSTUB;
          when "001111" => Result.Mnemo := SWAP;
          when "010000" => Result.Mnemo := LDA;
          when "010001" => Result.Mnemo := LDUBA;
          when "010010" => Result.Mnemo := LDUHA;
          when "010011" => Result.Mnemo := LDDA;
          when "010100" => Result.Mnemo := STA;
          when "010101" => Result.Mnemo := STBA;
          when "010110" => Result.Mnemo := STHA;
          when "010111" => Result.Mnemo := STDA;
          when "011001" => Result.Mnemo := LDSBA;
          when "011010" => Result.Mnemo := LDSHA;
          when "011101" => Result.Mnemo := LDSTUBA;
          when "011111" => Result.Mnemo := SWAPA;
          when "100000" => Result.Mnemo := LDF;
          when "100001" => Result.Mnemo := LDFSR;
          when "100011" => Result.Mnemo := LDDF;
          when "100100" => Result.Mnemo := STF;
          when "100101" => Result.Mnemo := STFSR;
          when "100110" => Result.Mnemo := STDFQ;
          when "100111" => Result.Mnemo := STDF;
          when "110000" => Result.Mnemo := LDC;
          when "110001" => Result.Mnemo := LDCSR;
          when "110011" => Result.Mnemo := LDDC;
          when "110100" => Result.Mnemo := STC;
          when "110101" => Result.Mnemo := STCSR;
          when "110110" => Result.Mnemo := STDCQ;
          when "110111" => Result.Mnemo := STDC;
          when others => 
            Result.Mnemo := ILLEGAL; -- Unknown and illegal instruction
        end case; -- op3
        
      when "10" => -------------- OP testing --------------
      
        case op3 is  -- 2nd level: OP + OP3 testing -------
          when "000000" => Result.Mnemo := ADD;
          when "000001" => Result.Mnemo := I_AND;
          when "000010" => Result.Mnemo := I_OR;
          when "000011" => Result.Mnemo := I_XOR;
          when "000100" => Result.Mnemo := SUB;
          when "000101" => Result.Mnemo := ANDN;
          when "000110" => Result.Mnemo := ORN;
          when "000111" => Result.Mnemo := XNOR;
          when "001000" => Result.Mnemo := ADDX;
          when "001010" => Result.Mnemo := UMUL; -- SPARC v.8
          when "001011" => Result.Mnemo := SMUL; -- SPARC v.8
          when "001100" => Result.Mnemo := SUBX;
          when "001110" => Result.Mnemo := UDIV; -- SPARC v.8
          when "001111" => Result.Mnemo := SDIV; -- SPARC v.8
          when "010000" => Result.Mnemo := ADDcc;
          when "010001" => Result.Mnemo := ANDcc;
          when "010010" => Result.Mnemo := ORcc;
          when "010011" => Result.Mnemo := XORcc;
          when "010100" => Result.Mnemo := SUBcc;
          when "010101" => Result.Mnemo := ANDNcc;
          when "010110" => Result.Mnemo := ORNcc;
          when "010111" => Result.Mnemo := XNORcc;
          when "011000" => Result.Mnemo := ADDXcc;
          when "011010" => Result.Mnemo := UMULcc; -- SPARC v.8
          when "011011" => Result.Mnemo := SMULcc; -- SPARC v.8
          when "011100" => Result.Mnemo := SUBXcc;
          when "011110" => Result.Mnemo := UDIVcc; -- SPARC v.8
          when "011111" => Result.Mnemo := SDIVcc; -- SPARC v.8
          when "100000" => Result.Mnemo := TADDcc;
          when "100001" => Result.Mnemo := TSUBcc;
          when "100010" => Result.Mnemo := TADDccTV;
          when "100011" => Result.Mnemo := TSUBccTV;
          when "100100" => Result.Mnemo := MULScc;
          when "100101" => Result.Mnemo := SLL;
          when "100110" => Result.Mnemo := SRL;
          when "100111" => Result.Mnemo := SRA;
          when "101000" => Result.Mnemo := RDY;
          when "101001" => Result.Mnemo := RDPSR;
          when "101010" => Result.Mnemo := RDWIM;
          when "101011" => Result.Mnemo := RDTBR;
          when "110000" => Result.Mnemo := WRY;
          when "110001" => Result.Mnemo := WRPSR;
          when "110010" => Result.Mnemo := WRWIM;
          when "110011" => Result.Mnemo := WRTBR;
          when "110100" => --- FPop1 instructions ---
            case opf is
              when "000000001" => Result.Mnemo := FMOVs;
              when "000000101" => Result.Mnemo := FNEGs;
              when "000001001" => Result.Mnemo := FABSs;
              when "000101001" => Result.Mnemo := FSQRTs;
              when "000101010" => Result.Mnemo := FSQRTd;
              when "000101011" => Result.Mnemo := FSQRTq;
              when "001000001" => Result.Mnemo := FADDs;
              when "001000010" => Result.Mnemo := FADDd;
              when "001000011" => Result.Mnemo := FADDq;
              when "001000101" => Result.Mnemo := FSUBs;
              when "001000110" => Result.Mnemo := FSUBd;
              when "001000111" => Result.Mnemo := FSUBq;
              when "001001001" => Result.Mnemo := FMULs;
              when "001001010" => Result.Mnemo := FMULd;
              when "001001011" => Result.Mnemo := FMULq;
              when "001001101" => Result.Mnemo := FDIVs;
              when "001001110" => Result.Mnemo := FDIVd;
              when "001001111" => Result.Mnemo := FDIVq;
              when "001101001" => Result.Mnemo := FsMULd; -- SPARC v.8
              when "001101110" => Result.Mnemo := FdMULq; -- SPARC v.8
              when "011000100" => Result.Mnemo := FiTOs;
              when "011000110" => Result.Mnemo := FdTOs;
              when "011000111" => Result.Mnemo := FqTOs;
              when "011001000" => Result.Mnemo := FiTOd;
              when "011001001" => Result.Mnemo := FsTOd;
              when "011001011" => Result.Mnemo := FqTOd;
              when "011001100" => Result.Mnemo := FiTOq;
              when "011001101" => Result.Mnemo := FsTOq;
              when "011001110" => Result.Mnemo := FdTOq;
              when "011010001" => Result.Mnemo := FsTOi;
              when "011010010" => Result.Mnemo := FdTOi;
              when "011010011" => Result.Mnemo := FqTOi;
              when others =>
                Result.Mnemo := ILLEGAL; -- Unknown and illegal instruction
            end case; -- opf
            
          when "110101" => --- FPop2 instructions ---
            case opf is
              when "001010001" => Result.Mnemo := FCMPs;
              when "001010010" => Result.Mnemo := FCMPd;
              when "001010011" => Result.Mnemo := FCMPq;
              when "001010101" => Result.Mnemo := FCMPEs;
              when "001010110" => Result.Mnemo := FCMPEd;
              when "001010111" => Result.Mnemo := FCMPEq;
              when others =>
                Result.Mnemo := ILLEGAL; -- Unknown and illegal instruction
            end case; -- opf
          
          when "110110" => Result.Mnemo := CPop1;
          when "110111" => Result.Mnemo := CPop2;
          when "111000" => Result.Mnemo := JMPL;
          when "111001" => Result.Mnemo := RETT;
          when "111010" => --- Ticc instructions ---
            case cond is  -- 3rd level
              when "0000" => Result.Mnemo := TN;
              when "0001" => Result.Mnemo := TE;
              when "0010" => Result.Mnemo := TLE;
              when "0011" => Result.Mnemo := TL;
              when "0100" => Result.Mnemo := TLEU;
              when "0101" => Result.Mnemo := TCS;
              when "0110" => Result.Mnemo := TNEG;
              when "0111" => Result.Mnemo := TVS;
              when "1000" => Result.Mnemo := TA;
              when "1001" => Result.Mnemo := TNE;
              when "1010" => Result.Mnemo := TG;
              when "1011" => Result.Mnemo := TGE;
              when "1100" => Result.Mnemo := TGU;
              when "1101" => Result.Mnemo := TCC;
              when "1110" => Result.Mnemo := TPOS;
              when "1111" => Result.Mnemo := TVC;
              when others => NULL;
            end case; -- cond
          
          when "111011" => Result.Mnemo := FLUSH;
          when "111100" => Result.Mnemo := SAVE;
          when "111101" => Result.Mnemo := RESTORE;
          when others =>
            Result.Mnemo := ILLEGAL; -- Unknown and illegal instruction
        end case; -- op3
        
      when "01" =>  -------------- OP testing --------------
        Result.Mnemo := CALL;
        Result.disp30 := disp30;
        
      when others => NULL;

    end case; -- op
      
    return Result;
  end Transcribe; -- function
  
  -------------------------------------
  function iccEvaluation(Mnemonic : SuperInstMnemonic;
                         icc      : std_logic_vector) return boolean is
  begin
  
    if ( 
      (Mnemonic = BA) or
      (Mnemonic = BNE  and icc(Z_ICC) = '0') or
      (Mnemonic = BE   and icc(Z_ICC) = '1') or
      (Mnemonic = BG   and (icc(Z_ICC) or (icc(N_ICC) xor icc(V_ICC))) = '0')or
      (Mnemonic = BLE  and (icc(Z_ICC) or (icc(N_ICC) xor icc(V_ICC))) = '1')or
      (Mnemonic = BGE  and (icc(N_ICC) xor icc(V_ICC)) = '0') or
      (Mnemonic = BL   and (icc(N_ICC) xor icc(V_ICC)) = '1')or
      (Mnemonic = BGU  and ((icc(C_ICC) = '0') and (icc(Z_ICC) = '0')) ) or
      (Mnemonic = BLEU and ((icc(C_ICC) = '1') or (icc(Z_ICC) = '1')) ) or
      (Mnemonic = BCC  and icc(C_ICC) = '0') or
      (Mnemonic = BCS  and icc(C_ICC) = '1') or
      (Mnemonic = BPOS and icc(N_ICC) = '0') or
      (Mnemonic = BNEG and icc(N_ICC) = '1') or
      (Mnemonic = BVC  and icc(V_ICC) = '0') or
      (Mnemonic = BVS  and icc(V_ICC) = '1') 
        ) then return TRUE;
    end if;
   
    return FALSE;
   
  end iccEvaluation; -- function
  
  -------------------------------------
  function TiccEval(Mnemonic : SuperInstMnemonic;
                    icc      : std_logic_vector) return boolean is
  begin
    
    if ( 
      (Mnemonic = TA) or
      (Mnemonic = TNE  and icc(Z_ICC) = '0') or
      (Mnemonic = TE   and icc(Z_ICC) = '1') or
      (Mnemonic = TG   and (icc(Z_ICC) or (icc(N_ICC) xor icc(V_ICC))) = '0')or
      (Mnemonic = TLE  and (icc(Z_ICC) or (icc(N_ICC) xor icc(V_ICC))) = '1')or
      (Mnemonic = TGE  and (icc(N_ICC) xor icc(V_ICC)) = '0') or
      (Mnemonic = TL   and (icc(N_ICC) xor icc(V_ICC)) = '1')or
      (Mnemonic = TGU  and ((icc(C_ICC) = '0') and (icc(Z_ICC) = '0')) ) or
      (Mnemonic = TLEU and ((icc(C_ICC) = '1') or (icc(Z_ICC) = '1')) ) or
      (Mnemonic = TCC  and icc(C_ICC) = '0') or
      (Mnemonic = TCS  and icc(C_ICC) = '1') or
      (Mnemonic = TPOS and icc(N_ICC) = '0') or
      (Mnemonic = TNEG and icc(N_ICC) = '1') or
      (Mnemonic = TVC  and icc(V_ICC) = '0') or
      (Mnemonic = TVS  and icc(V_ICC) = '1')
       ) then return TRUE;
    end if;
   
    return FALSE;
   
  end TiccEval; -- function
                         
  -------------------------------------
  function fccEvaluation(Mnemonic   : SuperInstMnemonic;
                         signal fcc : std_logic_vector) return boolean is
    variable E, L, G, U : boolean := FALSE;
    variable Local_fcc : std_logic_vector(1 downto 0) := fcc(1 downto 0);
  begin
    
    case Local_fcc(1 downto 0) is
      when "00" => E := TRUE; -- Equal
      when "01" => L := TRUE; -- Less
      when "10" => G := TRUE; -- Greater
      when "11" => U := TRUE; -- Unordered
      when others => NULL;
    end case; -- Local_fcc
    
    if (
      (Mnemonic = FBA) or
      (Mnemonic = FBU   and U) or
      (Mnemonic = FBG   and G) or
      (Mnemonic = FBUG  and (G or U) ) or
      (Mnemonic = FBL   and L) or
      (Mnemonic = FBUL  and (L or U) ) or
      (Mnemonic = FBLG  and (L or G) ) or
      (Mnemonic = FBNE  and (L or G or U) ) or
      (Mnemonic = FBE   and E ) or
      (Mnemonic = FBUE  and (E or U) ) or
      (Mnemonic = FBGE  and (E or G) ) or
      (Mnemonic = FBUGE and (E or G or U) ) or
      (Mnemonic = FBLE  and (E or L) ) or
      (Mnemonic = FBULE and (E or L or U) ) or
      (Mnemonic = FBO   and (E or L or G) )
       ) then return TRUE;
    end if;
    
    return FALSE;

  end fccEvaluation; -- function

  -------------------------------------
  function IURegDependency(rd    : natural;
                           InstB : Instruction) return boolean is
  begin
    if rd = 0 then return FALSE;
    end if;
    
    if IURs1Rs2AreIn(InstB.Mnemo) then
    
      if InstB.rs1 = rd then return TRUE;
      end if;
      
      if (InstB.i = 0 and InstB.rs2 = rd) then return TRUE;
      end if;
      
    end if;
    
    return FALSE;
  end IURegDependency; -- function
  
  -------------------------------------
--  function FPURegDependency(rd    : natural;
--                            Mnemo : SuperInstMnemonic;
--                            rs1   : natural;
--                            rs2   : natural) return boolean is
--    variable rd_quad, rs1_quad, rs2_quad : natural;
--    variable rd_double, rs1_double, rs2_double : natural;
--  begin
--    if IsFPop(Mnemo) then
--      if IsFPopDouble(Mnemo) then
--        rd_double  := rd/4;
--        rs1_double := rs1/4;
--        rs2_double := rs2/4;
--        if rs2_double = rd_double then return TRUE;
--        end if;
--        if FPURs1IsIn(Mnemo) then
--          if rs1_double = rd_double then return TRUE;
--          end if;
--        end if;
--      elsif IsFPopQuad(Mnemo) then
--        rd_quad  := rd/4;
--        rs1_quad 
<div align="center"><br /><script type="text/javascript"><!--
google_ad_client = "pub-7293844627074885";
//468x60, Created at 07. 11. 25
google_ad_slot = "8619794253";
google_ad_width = 468;
google_ad_height = 60;
//--></script>
<script type="text/javascript" src="http://pagead2.googlesyndication.com/pagead/show_ads.js">
</script><br />&nbsp;</div>