Previous Next Table of Contents

5. FAQ - Frequently Asked Questions

5.1 Why did you write this simulator?

I already had written the core of a small 6301 simulator, and needed a way to test 6811 and 6805 programs in a project. I tried some free and shareware simulators but found them buggy.

5.2 What is the difference between a simulator and an emulator?

Most definitions I have seen agree to the following:

"An emulator is essentially a simulator running in real time".

5.3 When can I benefit from using a simulator like this?

With these simulators, it is possible to test and debug new code in a controlled host environment.

5.4 What are the design ideas behind the simulator?

The design ideas are as follows: To be useable, the simulator should be easy enough to use, simulate correctly and fast enough. It should offer the possibility to verify all signals to/from the CPU on the logical level.

Ranking for useability:

  1. Correct simulation
  2. Easy to use
  3. Speed

5.5 Why is there no DOS version?

Earlier versions of the simulator compiled with Turbo C 2.0 some years ago. I have tried to compile the last version with Borland C++ 3.0, but got the following error message when linking:

Fatal: General error in module ../m68xx/io.c near module file offset 0x00000000
To compile, I had to turn off all warnings, so its possible that even if it would link, it would not run.

5.6 How can I compile under DOS?

I have listed the answers so that the supposed least work is first.

  1. You can compile using the DJGPP compiler that needs a standard DOS extender environment.
  2. You can use GNU make and your favorite DOS C/C++ compiler. The problem so far is that the latest versions of GNU make (>=3.70) does not seem to be ported to DOS.
  3. You can the make/build supplied with your favorite DOS C/C++ compiler. The shortest path to success here would be to make a subdirectory for each board, and let the compiler output all object files from the source tree in this directory.

5.7 Why are there so many directories?

It all started in a single directory for source, object and executable files. Then, it was splitted into many directories. Now, the directory structure is modeled similar to Linux with many directories that need to be traversed.

Separate source directories for framework and chip specific code, and a single object/executable directory for each chip specific board, looks as the best structure for this simulator.

5.8 How does the simulator simulate interrupt?

Before the fetching the next opcode, the simulator checks for simulated interrupt conditions and will transfer control to the interrupt vector with highest priority, if necessary.

5.9 What other simulators exist?

BSVC

BSVC is promising. Some commands:

2.0 has more "normal menu layouts" (File, Edit, ...) but basically the same functionality. Thus, no real 2.0.

For source debugging, an absolute listing file must be present. Symbols are not supported. No disassembly, but trace record for each instruction executed.

To use it with sim68xx, the following changes are needed:

Changes in sim68xx:

Changes in BSVC:

UMPS

Windows only.

NOICE

OK as model for sim68xx GUI. Global symbols.

tgdb

Couldnt get it running (tk4.1) Uses Tksteal, expect, wish and BLT.

5.10 How to simulate interrupt when using the simulator?

Normally by stopping the simulator and use a command that will cause a simulated interrupt event. Example:

5.11 How to simulate interrupt that happens when the simulator is running?

By sending characters to the standard input of the simulator.

The only way to get data into the simulator when it is running is to send the data to the simulator's standard input, which in most cases means the user must type in characters from the console. The simulator will poll standard input between the execution of each N'th instruction (currently N=50). If a character can be read from standard input, it will be sent to the input routine (io_in???) for the current device.

THERE IS CURRENTLY NO COMMAND TO CHANGE THE CURRENT INPUT DEVICE, IT IS ALWAYS SERIAL IN.

A more flexible input mechanism could use pseudo devices (fifos or sockets or similar in an unix environment).

5.12 How to get IO data into the simulator?

The following is possible without writing any new code:

All on-chip IO that does not require interrupt (parallel ports, SPI, SCI) can be simulated by Enter data into the (symbolic) IO address. Example:

The following is possible by writing a little code:

5.13 How to get IO data out from the simulator?

Ref. 'How to simulate interrupt that happens ...' above. Serial output (SCI) go to standard output in one of three modes as descibed below. Other output is not displayed in any form. To get it displayed, see the example section.

IO output modes sent to standard output:

  • Ascii (direct output)
  • Ascii with non-printable characters as backslash + hex
  • Hex
  • 5.14 What is the difference between the 6800, 6301, 6805 and 6811?

    6800 family

    The 6800 includes no on-chip IO. This was added later in the 6801, together with a set of new instructions.

    6301 family

    The 6301 is basically a clone of the 6801, with a few (about 5) new instructions. It is not binary compatible with the 6801/6811 because of the opcode conflict with the CPX/XGDX instructions.

    Quick ref. guide to sim. compability                    Arne Riiber 1995
    
    Chip differences
    ================
    6801, 6301      - ROM on chip
    6803, 6303      - ROM less
    68701, 63701    - EPROM on chip
    V or R          - 128 byte RAM
    X               - 192 byte RAM, 2 Output Compare, Timer2, Sync/async SCI
    Y               - 256 byte RAM, 2 Output Compare, Timer2, Sync/async SCI
    
    
            <-----6801-----><---------6301---------><--------6303---------->
            HD6801S HD6801V HD6301V HD6301X HD6301Y HD6303R HD6303X HD6303Y
    ROM     2K      4K      4K      4K      16K     -       -       -
    RAM     128     128     128     192     256     128     192     256
    Timer   1x16    1x16    1x16    1x16*   1x16*   1x16    1x16*   1x16*
    Timer2  -       -       -       1x8     1x8     -       1x8     1x8
    SCI     Async   Async   Async   Sync/as Sync/as Async   Sync/as Sync/as
    
            * = 2 Output Compare
    
    sim6301 supports 6801/6301V/6303R series, but not the second timer and
    sync. SCI on X and Y series.
    

    6805 family

    The 6805 adds some bit test instructions to the 6800 instruction set. It has 8 bit accumulator (A) and index register (X). The 68HC05C8 use the same SCI and SPI as the 68HC11.

    6811 family

    TO BE DONE!

    5.15 Are there any design notes?

    Yes, and they are included here.

    Design note 1

    ----------------------------------------------------------------------
    Command line options
    
    The simulator should have options like
            sim [options] filename
    where options are
            -Cxxx xxx is one of {6800, 6801, 6301, 6811e9, ...}
    that means each cpu has more or less different
            - number of regs available
            - opcodemap
            - hard registers
    
    ----------------------------------------------------------------------
    Memory interface
    
    Hard registers can be implemented with routines that provide
    read/write operations interface to memory:
            putmem (addr, value);           writemem (addr, value);
            value = getmem (addr);          value = readmem (addr);
    
    with the size variants for 8- and 16-bits:
            value = getbyte (addr);
            putbyte (addr, value);
    
            value = getword (addr);
            putword (addr);
    
    These routines must take special actions if address references
    a hard register. The actions may be different for each cpu type.
    
    Q:
            a) NOW WHO IS GOING TO FEED THESE ROUTINES WITH addr?
            b) AND WHO IS GOING TO UPDATE THE PROGRAM COUNTER?
    
    A:
    a) To give the best conditions to rules in section Detailed execution,
    each little routine that implements an instruction
    could at the detail level set the pc in small steps.
    
    Addr could be taken directly from the current program counter (pc),
    opcode   = getbyte (cpu.pc);
    operand1 = getbyte (cpu.pc+1) (if any),
    operand2 = getbyte (cpu.pc+2) (if any), 
    
    b) Since some instructions (Bxx, JSR, JMP, RTS, SWI..)
    directly modifies the pc, the functions that implements instructions
    can modify the pc directly or return the new pc to the caller.
    
    The principal main loop would be
    
    cpuregs cpu;
    /* uchar   mem[65535]; interface via get/put[byte|word] */
    
    main()
    {
            fillmem (argv[1], mem); /* fill mem with
            for (;;)
                    exec_instr (opcodemap [getbyte (cpu.pc)]);
    }
    
    ----------------------------------------------------------------------
    
    Detailed execution
    
    A detailed model of the cpu would include the actions taken
    at each clock cycle. A simple implementation could be
    
    ldaa_imm ()
    {
            step1;
            clock(1);
            step2;
            clock(1);
            :
            stepN;
            clock(1);
    }
    
    This allow clock() to interrupt execution before an instruction
    is completed. Each instruction can be more or less detailed,
    thus allowing writing instruction in a coarse way first, like
    
    ldaa_imm ()
    {
            step1_N;
            clock(N);
    }
    ----------------------------------------------------------------------
    This part describes two possible solutions for decoding
    addressing mode.
    
    1) Storing addressing mode in an opcode array
            - Faster than 2)
            - Requires more storage than 2)
            - Constant delay
    
    2) Decoding addressing mode from the opcode
            - Delay varies, addressing mode can be done within 16 tests
            - slower than 1)
            - Requires less storage than 1)
    
    
    C code:
    1) Opcode table:
            :
            {0x02, 0, idiv,         inherent,       41,     "idiv"},
            :
    
    2)
            switch (*pc & 0xF0) {
                    case 0x10: /* inherent */
                    case 0x20: /* inherent, direct or indexed_x */
                    case 0x30: /* relative          */
                    case 0x40: /* A:inherent        */
                    case 0x50: /* B:inherent        */
                    case 0x60: /* indexed_x         */
                    case 0x70: /* extended          */
                    case 0x80: /* A:immediate       */
                    case 0x90: /* A:direct          */
                    case 0xa0: /* A:indexed_x       */
                    case 0xb0: /* A:extended        */
                    case 0xc0: /* B:immediate       */
                    case 0xd0: /* B:direct          */
                    case 0xe0: /* B:indexed_x       */
                    case 0xf0: /* B:extended        */
            }
    
    ----------------------------------------------------------------------
    Condition code register
    
    Below is a list of (flags, instructions) for all instructions
    that affects the same CCR flag bits
    (Except for instructions like CLI, CLV, ... where an unique
    instruction affect a single flag only.)
    
    Shift left/right instructions rotate either
    MSBit or LSBit into the C flag.
    
    Q: Is sub8(a,b) equivalent to add8(a,-b) (including flag settings)?
    
    CCR flags
    SXHINZVC        Instructions                    Comment
    ========        =======================         ===========================
    --H-NZVC        ABA,ADCA,ADCB,ADDA,ADDB         Flags set in add()
    
            /* Use set_nzvc_8/16(v1,v2) for all instr. that affect NZVC? */
    
    ----NZVC        ADDD,                           Flags set in add16()
                    ASL/LSL,ASLA/LSLA,              6)
                    ASLB/LSLB,ASLD/LSLD,            6)
                    ASRA,ASRB,                      6)
                    CBA,CMPA,CMPB,                  Flags set in sub8()
                    CPD,CPX,CPY,                    Flags set in sub16()
                    DAA,                            3)
                    NEG,NEGA,NEGB                   1) 2)
                    ROL,ROLA,RORB                   6)
                    SBA,SBCA,SBCB,                  Flags set in sub()
                    SUBA,SUBB,SUBD                  Flags set in sub()
    
    ----NZ0-        ANDA,ANDB,                      Flags set with 
                    BCLR,BITA,BITB,BSET,            bittest8/16(value)
                    EORA,EORB,
                    LDAA,LDAB,LDD,LDS,LDX,LDY,
                    ORAA,ORAB,
                    STAA,STAB,STD,STS,STX,STY
                    TAB,TBA
    
    ----0100        CLR,CLRA,CLRB                   Flags set to 0x04 in clrbyte()
    
    ----NZ01        COM,COMA,COMB                   Flags set in com()
                                                    {bittest();sec();}
    
    ----NZV-        DEC,DECA,DECB,                  4) Flags set in dec8()?
                    INC,INCA,INCB                   5) Flags set in inc8()?
    
    -----Z--        DEX,DEY,INX,INY                 Flags set in inc16()
    
    -----ZVC        FDIV                            Flag set in div()
    
    -----Z0C        IDIV                            -"-
    
    ----0ZVC        LSR,LSRA,LSRB,LSRD              6)
    
    -------C        MUL                             11)
    
    SXHINZVC        RTI,TAP                         All flags set
    
    ----NZ00        TST,TSTA,TSTB                   Flags set in tst():
                                                    {bittest();clc();}
    
    
    
    Note (6301, assumed to be valid for 6811 too):
    ----------------------------------------------
    1)      NEG:            V = (result == 0x80);
    2)      NEG:            C = (result != 0x00);
    3)      DAA:            C = (C | BCD(msnibble(result)) > 9)
    4)      DEC:            V = (op before dec == 0x80)
    5)      INC:            V = (op before dec == 0x7F)
    6)      SHL,SHR:        V = (result.N xor result.C == 1)
    7)      LDX,LDS/STX/STS N = (result.bit15 == 1)
    11)     MUL:            C = (result.bit7 == 1)
    
    
    
     *  The addbyte and addword routines should be verified against a real cpu
     *
     *  CCR registers affected:
     *
     *      CCR_C = 1 if `val1' + `val2' + `carry' exceeds 255 (unsigned)
     *              0 else
     *      CCR_V = 1 if `val1' and `val2' has the same sign and
     *              the sign of `val1' + `val2' + `carry' is different
     *              (which means result is not a valid signed number),
     *              0 else
     *      CCR_N = sign of result
     *      CCR_Z = 1 if val1 + val2 is zero, else 0
     *      CCR_H = 1 if the addition of the lower nibbles of val1 and val2
     *              exceeds 0x0F.
    
     *
     *  The addbyte and addword routines should be verified against a real cpu
     *
     *  CCR registers affected:
     *
     *      CCR_C = 1 if `val1' + `val2' + `carry' exceeds 65535 (unsigned)
     *              0 else
     *      CCR_V = 1 if `val1' and `val2' has the same sign and
     *              the sign of `val1' + `val2' + `carry' is different
     *              (which means result is not a valid signed number),
     *              0 else
     *      CCR_N = sign of result
     *      CCR_Z = 1 if val1 + val2 is zero, else 0
     *      CCR_H = 1 if ??
    
    struct cpuregs {
            enum cputypes cputype;  /* Good or bad? what with hard regs? */
            struct acc {
                    unsigned a:8;
                    unsigned b:8;
            } acc;
            /*
             * By specifying 16 bits registers, result of additions etc.
             * will wrap-around the 64K range.
             * It may give a decrease in speed.
             */
            unsigned ix:16;
            unsigned iy:16;         /* 6811 only */
            unsigned sp:16;
            unsigned pc:16;
            /*
             * By avoiding bit flags, we
            unsigned char cflag;
            unsigned char 
            /*
             * Most of the time, the flags will be set by LDAA/STAA
             * type instructions, and not TAP. Thus the most efficient
             * way to update flags would be:
             *        Z: if (val) ccr |= ZFLAG; else ccr &= ~ZFLAG;
             *        or ccr.z = (val == 0);
             *
             * It's undefined how a C compiler assigns the bit fields
             * => is #define'd bit masks more portable?
             *    Yes: (u_char) CCR and (u_char) MEM have the same storage
             *         layout.
             * Conclusion: If we need to transfer A -> CCR,
             * we can do it in one operation with (u_char) CCR,
             * else we must for each 
             *      #define V 0x04
             *      :
             *      setvflag(A & V)...; /* cpu.ccr = (A & V != 0); */
             *      :
             */
            struct ccr {
                    unsigned c:1;   /* Carry/Borrow flag */
                    unsigned v:1;   /* Overflow flag */
                    unsigned z:1;   /* Zero flag */
                    unsigned i:1;   /* Interrupt disabled flag */
                    unsigned h:1;   /* Half carry flag (from bit 3) */
                    unsigned x:1;   /* X-interrupt disabled flag */
                    unsigned s:1;   /* Stop disable flag */
            } ccr;
    
            /*
             *  Debug registers: stack limits
             */
            struct {
                    unsigned min;
                    unsigned max;
            } stack;
    };
            /*
             * Get opcode from memory,
             * inc program counter to point to first operand
            /*
             * Decode and execute the opcode.
             *
             * By updating clock here, the same functions can be called
             * for (nearly) opcode compatible architectures (like 6301,
             * 6811) with different instr. cycle counts, at least
             * as long as the cycle count is constant.
             *
             * We don't care in detail about how each instruction
             * is executed, we just wait to update the cycle here.
             *
             * The function called must update the program counter
             * to the address of the the next instruction.
             */
             */
    

    Design note 2

    1. Reducing number of files involved.
    2. Logical grouping of functions.
    
      2.1
    
      Let each cpu variant (6800, 6801, 6301, 6805, 6811) have its
      own 6800map.c, 6801map.c, 6301map.c, 6805map.c, 6811map.c.
      68xxmap.h can be a common include file containing the common
      struct opcodemap, getopcodep().
    
      Remove the 68xxext.h files - the functions are only used in 68xxmap.c
      Q: Should we also move 68xxext.c functions into a common file?
      A: The 6800/6801/6301/6811 functions may be merged into a common file.
         The 6805 functions are basically different (8-bits X-reg).
    
      Name proposals:
        m6800_aba_inh()
        m6800_adca_imm()
        :
        m6805_neg_ix0()
        :
        m6811_ldy_imm()
    
      These naming conventions clearly show the source module (m6800.c,
      m6801.c, m6801.c, m6805.c, m6811.c)
      Use -DNOMAP to not include the opcode map and the opcode map functions.
      All opcode maps could be of the most general type (m6811).
    
    
      2.2 CPU access
    
      CPU access should be done through the routines
        cpu_getreg_[a|b|x|y|pc|sp|ccr]      (or just cpu_get_[a|b|x|y|pc|sp|ccr])
        cpu_setreg_[a|b|x|y|pc|sp|ccr]
      in module cpu.c, to distinguish it from bittestbyte() etc.
      bittestbyte() and similar functions should also be renamed.
    
    
      2.3. Memory access
    
      Memory access should be done through the functions
        mem_getb (addr)
        mem_getw (addr)
        mem_setb (addr, val)
        mem_setw (addr, val)
    
    
      2.4. Arithmetic/logical operations
    
      Today, most of these operations are in the file basic.c.
      (addbyte/addword, ...) together with a couple of warning/error
      debug support function connected to push/pop.
      A more proper name would be alu.c, and it should be as "clean"
      as possible.
    
    
      3. Modules
    
        Module      Contents
        -------     --------
    
        cpu.c       cpu_getreg_[a,b,x,y,pc,sp,ccr]  ;Register access
                    cpu_setreg_[a,b,x,y,pc,sp,ccr]
                    cpu_getncycles()
                    cpu_getstackmin()
                    cpu_printregs
        alu.c       alu_add_bytes (left, right, dest)
                    alu_add_words (left, right, dest)
        m6301.c     m6301_aim_imm(), m6301_tim_imm(), ...
        m6800.c     m6800_aba_inh(), m6800_adca_imm(), ...
        m6801.c     m6801_abx_inh(), m6801_addd_imm(), ...
        m6805.c     m6805_brset0_btb(), ...
        m6811.c     m6811_aby_inh(), ...
        m68xx.c     m68xx_addbyte (b1, b2), m68xx_testbyte (b), ...
                    m68xx_negaddr (addr)
        mem.c       mem_getbyte (addr)
                    mem_setbyte (addr, value)
                    mem_fprint (fp, addr, nbytes) - display memory contents
        io.c        io_install ()
        ??.c        m6800_unassemble (addr)
                    m6801_unassemble (addr)
                    m6805_unassemble (addr)
        ??.c        single_step() - generic
      
      6811[A0,A1,A8,E0,E1,E9]:  
        CPU core: extended 6800/6801
    
                                    Strongly connected to:
                                    Ports   Interrupts
        Memory (RAM/ROM/EPROM)      Y       Y
        Timer System                Y       Y
        SPI                         Y       Y
        SCI                         Y       Y
        
        The strong connection sugessts a single file
        Why not a single 6811 file with all aby_inh(), opcode map,
        etc?
    
        Make a (big) drawing of all the visible/non-visible functions.
        Interaction with environment. Different processor architectures.
        Encapsulate as appropriate.
    
    
      Separate a) cpu specific stuff (regs, instructions), b) on-chip IO
      Should be easy to fill in tables or similar to adapt to a new cpu.
      Could be:
    
            m6301/instr.c           6301 instructions (extensions)
            m6301/tables.c          Tables for opcode, interrupts, on-chip IO
            m6301/memmap.c          Memory map (incl. IO + interrupts?)
            m6301/io.c              On-chip io functions (SCI, timers)
            m6301/
            m6811/
            m6811/
            m6805/
            m6805/
    
      General routines, inheritance
                    - Avoid indirect function calls where direct can be used,
                      i.e. single_step()
                    - single_step() must check for interrupts => chip dependant
                    - unassemble() { call cpu specific function ptr, m6811_unassemble}
    
                    
    =========================================================================
    IDEAS
    
    Some not-so-important ideas:
    
    Install the routine to be called when the processor
    wants to output a byte from the SCI. The default routine
    should call putchar() or write (fileno(stdout), buf, nbytes)
    
    To increase efficiency, a buffered approach should be used,
    but how to determine when to flush the buffer?
    This is application specific. The default application should
    flush after each byte, and a specific application may install
    own logic around the SCI output using io_install().
    Example: io_nc24r: flushing after each 6 byte.
    
    We could add a stderr channel to the processor reg. dump
    routines. This channel could be an address in the processor's
    memory map. Problem: when operating in simulated env.,
    the reg. dump is outputted to both SCI (net) and stderr.
    
    Or install a hook into the SWI vector???
    When SWI is executed, redirect SCI output to stderr,
    don't let it go to the net.
    
    
    Using SCI as stdin/stdout/stderr
    --------------------------------
    
    Useful for cpu monitor programs that runs interactively with user connected
    to SCI of the cpu.
    CPU running:
            read from sci <=> read from stdin
                    problem:
                            let cpu do full work when no characters typed
                    solutions:
                            a) Assume monitor programs programs doesn't do much
                            work except for polling (false: download!)
                            poll stdin between each instruction.
                            b) Use select() with null timeout between each
                            instruction. Adds overhead and flexibility: sci
                            and spi (and other io-ports) become reachable
                            from other processes as separate files.
                            c) Use SIGIO. Does't work on some systems (linux)
    
                            Solutions b) and c) in general work on unix systems,
                            but are not portable to simpler platforms (do$ etc)
            write to sci <=> write to stdout
                    easy.
    

    Design note 3

    Makefile targets:
    General cpu:
            sim6800
            sim6801
            sim6301
            sim6805
            sim6811
    Application specific:
            simnccpu
    
    
    Procedure for adding new simulator targets:
    General cpu:
            68xx type cpu chip:
                    Add subdir src/68xx/CHIP
                    where CHIP is the name of the cpu type
                    Example: src/68xx/6816
            Other:
                    Add subdir src/FAMILY/CHIP
                    Example: src/80xx/8086
            
    Application specific:
            Create file src/FAMILY/usr/APP
            where
                    FAMILY is the name of the cpu family (f.ex. 68xx)
                    APP is the name of the file containing application specific
                    code.
            Example:
                    src/68xx/usr/nccpu contains application specific code for
                    a simulator of NC-CPU card w/6811 chip.
    
    Common:
            Add target to src/makefile.
    
    Procedure for making target:
            Enter directory src.
            Type 'make' to make all targets
            or   'make TARGET' where TARGET is the name of a specific target.
    
    
    Instruction set hierarchy:
    
    6800
     |    (subset)
     +-----------+
     |          6805
    6801
     |
     +----+
     |    |
    6301 6811
    
    A better figure would show this as sets with unions and intersections.
    
    
    Inheritance
            sim6800 Bare bone mother of Motorola CPU's simulated
            sim6801 Inherits 6800
                    On-chip ports, timer, sci.
            sim6301 Inherits 6800, 6801
                    Main difference to 6801 are a few instructions.
            sim6805 Inherits 6800
                    Same spi as 6811.
            sim6811 Inherits 6800, 6801
    
    Application specific:
            simnccpu Simulates 6811 w/additional equipment connected to I/O
    
    Implementation:
            opfunc.c        Unique functions simulating instruction execution.
            optab.c         Table of pointers to instruction executing functions.
    

    Design note 4 - results of inlining

    INLINING
    
    To increase execution speed to a level practical for testing of
    real programs in a simulated environment, inlining was performed
    on the simulator in stages.
    
    gcc flags: -O2 -finline-functions:
    Time in seconds (16MHz 386 @2.0 BogoMIPS)
    
    Step:                                   A   B      C      D        E
    Macroized/inlined:                      -   +reg.h +cpu.h +mem.h   +spi.h
                                                              +ireg.h  +sci.h
                                                                       +timer.h
    
    simnccpu ~/nc2/ncr/test/delaytest.s19:  3   a)                       1.5
    
    simncpan ~/nc2/ncp/test/testdip.s19:    46  32      31     22        20
    simncpan ~/nc2/ncp/6805-smallc/ncp.s19  32                 16        15
    
    a) Simulator runtime errors
       (as result of cc flags?)
       No, bug in macro reg_setaccd().
    
    COMMENTS
    
    Simulation of NC-PAN gained a performance increase to about double speed
    when inlining/macros was implemented.
    
    With no inlining, simncpan ~/nc2/ncp/6805-smallc/ncp.s19 had a blink time
    of about 32s. With inlining, time was reduced to about 16s.
    
    Considering the step from D to E, 3 function calls were inlined, with a
    speed increase of about 10%. Each of these functions is called at most
    once per instruction.
    
    At stage E, there are about 2 more functions that can be inlined
    (instr_exec() and timer_inc()), which is expected to give another
    10% speed increase.
    
    The relative changes in speed follows the number of times a
    function is called. The reg/ireg/mem functions are often called,
    (how many times per instruction? Min:.. Max:.. Average:.. )
    inlining them gave most impact on execution speed.
    

    Design note 5 - character user interface

    Suggested layout for sim68xx tool
    
    1996-06-25/AR
    ------------------------------------------------------------------------------
    File    Memory          Run             Breakpoint
    ->Load  ->Display       ->Trace         ->List
    ->Exit  ->Modify        ->Step over     ->Set
                            ->Go            ->On error
                            ->Reset         ->On warning
    View            Edit
    ->Memory        ->Memory
    ->Register      ->Register
    ->Breakpoints   ->Breakpoints
    
    
    Windows:
            Register
            Asm/src
            Memory
            Callstack
            IO
    
    
    1996-08-12/AR   Suggested window contents
    -------------------------------------------------------------------------------
    Register Window (~ = input field too)
            PC=0000 A:B=0000 X=0000 Y=0000 SP=0000 CCR=d0(SXhInzvc) [0]
               ~~~~     ~~~~   ~~~~   ~~~~    ~~~~     ~~
    Memory Window
            Output
            aaa0 h0 h1 h2 h3 h4 h5 h6 h7 h8 h9 ha hb hc hd he hf   0123456789abcdef
            aaa1 h0 h1 h2 h3 h4 h5 h6 h7 h8 h9 ha hb hc hd he hf   0123456789abcdef
            aaa2 h0 h1 h2 h3 h4 h5 h6 h7 h8 h9 ha hb hc hd he hf   0123456789abcdef
            aaa3 h0 h1 h2 h3 h4 h5 h6 h7 h8 h9 ha hb hc hd he hf   0123456789abcdef
            aaa4 h0 h1 h2 h3 h4 h5 h6 h7 h8 h9 ha hb hc hd he hf   0123456789abcdef
    
            Input
            aaan        h0 h1 h2 ... hf
            ~~~~~~~~~~~ ~~~~~~~~~~~~~~~
            Comment: symbol may be used instead of address 'aaan'
    
    Callstack
            aaa1    f1      sym1
            aaa2    f2      sym2
            aaa3    f3      sym3
    
    Asm/src - should display current subroutine too!
    
            911f    3c             pshx
            9120    bd af a1       jsr   afa1       _timer_init
            9123    38             pulx
            9124    bd a1 48       jsr   a148       _net_init
            9127    bd 93 56       jsr   9356       _func_init
            912a    ce 00 09       ldx  #0009
            912d    3c             pshx
            912e    ce 14 43       ldx  #1443       _buttons
            9131    3c             pshx
            9132    bd b8 f2       jsr   b8f2       _relay_read
    
            To get C or asm source intermixed, the file and the line
            number must be available, either in the executable,
            or as a file containing lines with the information
                    address file line
            Changes required:
                    Motorola freeware asm:
                            Output file while source is processed
                    Gcc/aslink:
                            Modify gcc, asXXXX, aslink.
    
    1996-08-20/AR
    ------------------------------------------------------------------------------
    Breakpoints
            Edit->
                    Input
                    aaan
                    ~~~~~~~~~~~
                    [Set] [Clear] [Cancel]
            View
    
            Output
            aaan    symbol
            :
    
            Comment: symbol may be used instead of address 'aaan'
                    This is a typical list operation?
                            Set=AddToList, Clear=DeleteFromList
            +-Breakpoints-------------------+
            |       Address Symbol          +
            |       +---------------+       |
            |       | aaan  symbol  A       |
            |       |               |       |
            |       |               v       |
            |       +---------------+       |
            |       +---------------+       |
            |       | _printf       |       |
            |       +~~~~~~~~~~~~~~~+       |
            |       [Add] [Delete]          |
            +-------------------------------+
    
    Implemetation solutions
    
            o Use sim68xx as a backend to gdb/tkgdb.
                    This is more a solution for stepping C/C++ source,
                    typically in a Unix environment.
            o Use curses to be portable
                    Can translate Mouse events to keypresses in X
                    Is this possible in dos/windows environments?
            o Use Tcl/Tk
                    o let sim68xx commands be part of Tcl/Tk interpreter
                            + Available on many platforms
                            + Easy customizable
                            - Tight integration
                                    (must be compatible w/Tk version)
                    o Use TkSteal
                            Can start the simulator as a process
                            in a window and send keypushes to it,
                            similar to tty window in Xview
            o Use WxWin that has many back ends
                    Xview, Curses, Windows
    
            It should be possible to send commands between separate types
            and instances of sim68xx to simulate the communication on a
            serial line. This is possible with
    
                    o Unix like IPC and command line driven interface
                            IPC can be pipe or socket.
                            Sockets are also now avilable in Windows.
                    o Tcl/Tk in Unix environment:
                            o Command line interface and TkSteal
                                    Works in Unix
                            o Integrated with Tk
                                    Also works in Windows?
    
            There is one question related to implementing sim68xx as a part of Tk.
            Will a running copy of tksim68xx block the user interface?
            The job of a running simulator is to run as fast as it can,
            must a poll-back to Tk be implemented in the execution loop?
            Today, the command line driven sim68xx does a poll for IO
            after the interpretation of some (say 50) instructions.
    

    Design note 6 - how the SPI is simulated

    
    1997-01-24/A.Riiber
    
    Mechanism for simulating SPI input/output
    -----------------------------------------
    
    DATA FLOW
    
           user data in `buf'
                |
                | spi_in(buf, buflen) /* user wants to clock in data to SPI */
                |
                V
     0 1 ... spi_rx_nbytes
    +----------------------
    | spi_rx_buffer                 /* Data is stored until CPU is ready */
    +----------------------
             |
             | spdr_putb()          /* CPU writes to SPI data register */
             v                      /* Data is transferred from buffer to SPDR */
          +------+
          | SPDR |
          +------+
             |
             | spdr_getb()          /* CPU reads from SPI data register */
             v
    
    DESCRIPTION
    
    The user calls spi_in() to enter data to send into the SPI.
    Each time spi_putb(SPDR) is called, a byte is transferred to the SPI data
    register SPDR. SPDR can be read from the CPU by calling spi_getb(SPDR).
    

    Design note 7 - I2C

    
    I2C protocol
    ============
    
    - Data transfer is initiated  with START
    - Each byte transferred must be ACK'ed by receiver (whether master or slave)
    - Data transfer is terminated with STOP or a new START
    
      
    1. Master sends data to slave
    -----------------------------
    
      1         7        1    1  8         1        8      1   1   <- bits
          +----------------+     +------+        +------+
    START | ADDRESS | R/~W | ACK | DATA | ACK .. | DATA | ACK STOP
          +----------------+     +------+        +------+
                       '0'        <----n data bytes----->
    
    2. Master reads data from slave
    -------------------------------
    
      1         7        1    1  8         1        8      1   1   <- bits
          +----------------+     +------+        +------+
    START | ADDRESS | R/~W | ACK | DATA | ACK .. | DATA | ACK STOP
          +----------------+     +------+        +------+
                       '1'        <----n data bytes----->
    
    3. Address format
    -----------------
    
    MSB     R/W~
    
    0000 000 0      General call address. Next byte follows:
                    a)      02h   - Enter mode to get slave address from SW
                    b)      04h   - Latch slave address from HW
                            06h   - Reset + a) + b)
                            other - Reserved, ignore
    0000 000 1      General call address. Next byte is master's address.
    
    0000 001 x      CBUS address
    0000 010 x      -+
     :               +- Reserved
    0000 111 x      -+
    
    0001 xxx x       -+
     :                +- Vendor addresses
    1110 xxx x       -+
    
    1111 xxx x      Reserved for future extension
    
    
    Xicor X9241
    ============
    
    1. Master sends data to slave
    -----------------------------
    
      1      4        4       1     8      1        8      1   1   <- bits
          +-------+--------+     +------+        +------+
    START |    ADDRESS     | ACK | CMD  | ACK .. | DATA | ACK STOP
          +-------+--------+     +------+        +------+
            0x09   instance       <----n data bytes----->
    
    
    Data direction is given by the command byte (CMD).
    Are there generalities in this Xicor specific protocol?
    
    CMD
    
    Each instance has 4 potmerers.
    Each potmeter (P) has a wiper and 4 NVRAM registers (R).
    
      4     2   2   <- bits
    +-----+---+---+ +----+
    |instr|pot|reg| |Data|  Mnemonic        Description
    +-----+---+---+ +----+
      1     -    R    -     RESTORE_WIPERS  Transfer R to wiper for all potmeters
      2     P    -    1     INC_DEC_WIPER   Inc/dec wiper for potmeter P
      8     -    R    -     STORE_WIPERS    Transfer wiper to R for all potmeters
      9     P    -    r     READ_WIPER      Read wiper for potmeter P
      a     P    -    w     WRITE_WIPER     Write wiper for potmeter P
      b     P    R    r     READ_STORE      Read reg R for potmeter P
      c     P    R    w     WRITE_STORE     Write reg R for potmeter P
      d     P    R    -     RESTORE_WIPER   Transfer R->P
      e     P    R    -     STORE_WIPER     Transfer P->R
     other                  Undefined
    
    1 = 1 bits data, sampled on each clock transition, unlimited length,
        no ack, terminated by stop
    r = 8 bits data from slave to master
    w = 8 bits data from master to slave
    
    Suitable API:
    
    write_wiper (pot, val);
    read_wiper  (pot, &val);
    
    store_wipers   (reg);
    restore_wipers (reg);
    store_wiper    (pot, reg); /* Could have param pot=ALL_WIPERS */
    restore_wiper  (pot, reg); /* -"- */
    read_store     (pot, reg, &val);
    write_store    (pot, reg, val);
    
    inc_wiper (pot, step); /* +/- */
    


    Previous Next Table of Contents