Couch to 64k Part 5: Adding RAM and a CP/M Compatible Memory Architecture to the Z80 Breadboard Computer

If you’ve been following this series so far then you’ll have a basic Z80 based computer with ROM, an LCD display and a keypad or keyboard. What we don’t have yet is any way store store data. We need to add some RAM (Random Access Memory). This is what I’ll be focusing on in this part. I also want to look ahead at the possibility of being able to run CP/M on the machine so I’ll be looking at what we need to design in to the memory map to make that feasible. (But bear in mind we’ll need to do more later to make CP/M fully supportable).

Parts Needed

Additional parts needed for this article are:

  • 621024 or 628128 128K by 8 bit SRAM
  • 74LS32 Quad 2-input OR gate
  • 74LS74 Dual D-type flip-flop

See the end of the article for buying links.

RAM Basics

Once you know that ROM stands for read-only memory then you’d think that RAM would be called Read-Write Memory, or something similar. Since both RAM and ROM are random access the naming scheme makes no sense.

The word ‘random’ is used in contrast to ‘sequential’ as in Sequential Access Memory. In sequential access memory each data bit is accessed in turn. The memory is advanced from one bit to the next but the only way to go back to the previous bit is the cycle through every other bit in between. This is, of course, very slow but there was a time in the 1960s when sequential access memory chips where cheaper and more readily available than RAM chips. Indeed the very first desktop computer, the Datapoint 22001, used sequential access memory.

Another snippet of history is that the types of memory chips used in the ’70s and ’80s had fewer address lines than they needed. E.g. the 4164 stored 64k bits of memory. It could store (or read) a single bit at a time and computers would use eight in parallel to store bytes. However, it only had eight address lines. The hardware designer would have to multiplex2 the address bus between the upper eight bits and the lower eight bits of the address.3

I mention this so you’ll have a better chance of understanding what’s happening if you ever look at the schematics of old computers. This may also make you realise how lucky we now are to have a single chip which can store 64k bytes or more of memory with ample address lines and eight data lines.

DRAM Versus SRAM

You can also be thankful that we now have plentiful, affordable, SRAM chips. SRAM stands for Static RAM. The data we write to it will stay there until we switch the power off. Contrast this with DRAM.

Back in the seventies and eighties SRAM was too expensive to be practical and most computers used DRAM, or Dymamic RAM instead. Dynamic RAM only remembers it’s contents for a fraction of a second and needs to be constantly ‘refreshed’. Refreshing entails the hardware designer building a circuit which cycles through each each row address in turn and alternates memory access between the CPU and the refresh cycle.

You may remember from part 1 of this series that the Z80 includes the ability to do this and save the hardware designer some work. This is the purpose of the Z80s RFSH (refresh) pin. When the refresh pin is asserted the lower 7 bits4 of the address bus contain the value of the R (refresh) register. The R register is increased by one after each refresh cycle.

But that’s enough history let’s return to designing our computer.

Designing a Memory Map

We want our computer to contain both RAM and ROM. We therefore need to decide which memory addresses will be ROM and which will be RAM.

The Z80 when reset always begins executing code at address $0000. It therefore makes sense to put ROM at the bottom of the memory map (addresses beginning with $0000) and, therefore, have RAM at higher memory addresses. We’re using a 32k ROM chip so we could have a 50:50 split between 32k ROM (addresses $0000-$7fff) and 32k of RAM at addresses $8000 to $ffff.

While that’s probably plenty for our purposes here I feel it’s more realistic to have less ROM and more RAM. I am, therefore, going to design our computer to have 16k ROM and 48k of RAM with ROM at addresses $0000 to $3fff and RAM at addresses $4000 to $ffff.

A basic memory map divided into four 16Kb blocks
A basic memory map divided into four 16Kb blocks

Memory Address Decoding

When we designed our I/O system we needed a way to enable the appropriate device depending on the I/O address. We now need to do the same to enable either ROM or RAM depending on the memory address being accessed.

Given our memory map from the previous section we need to enable the ROM if address lines A15 and A14 are both low. Any other combination of A15 and A14 will access RAM.

If we OR A15 and A14 together we get a low when, and only when, both A15 and A14 are low. This will be our selection signal which we can refer to as /USE_ROM

Our current EEPROM schematic - note the /CS pin connection to /MREQ.
Our current EEPROM schematic – note the /CS pin connection.

If we look at the available input signals on the ROM IC we have /WE (write enable), /RD (read) and /CS (chip select). Write enable is permanently disabled by being connected to 5V and /RD is connected to the Z80’s /RD signal. That leaves us the /CS signal to control when the ROM is enabled.

We currently have that pin connected directly to the Z80’s MREQ (memory request) signal. However, we now only want that pin to be asserted when both our /USE_ROM and /MREQ signals are asserted. Since both these signals are inverted we can use the inverted logic version of an AND gate – an OR gate.

Schematic to enable the ROM when A15 and A14 are both zero
Schematic to enable the ROM when A15 and A14 are both zero

The signal for the RAM is somewhat easier. The chip I am using has two chip select signals, /CS1 which is active low and CS2 which is active high. We can connect the /MREQ signal directly to the active low chip enable, and the /USE_ROM signal we generated above to the RAM’s active high chip select input.

Thus, if either (or both) A15 or A14 is high then the /USE_ROM signal will be high and the RAM chip will be selected when both /MREQ is low and /USE_ROM is high. The truth table below shows which device will be active at any one times with the relevant chip select signal(s) shown in bold.

/MREQ A15 A14 /ROM_CS /RAM_CS1 RAM_CS2
0     0   0   0       0       0        ROM active
0     0   1   1       0       1        RAM active
0     1   0   1       0       1        RAM active
0     1   1   1       0       1        RAM active
1     0   0   1       1       0        Neither active
1     0   1   1       1       1        Neither active
1     1   0   1       1       1        Neither active
1     1   1   1       1       1        Neither active
Control signal schematic for a basic Z80 memory model
Control signal schematic for a basic Z80 memory model

Preparing for CP/M

CP/M was a popular operating system for Z80 computers. If we can add support for CP/M then it opens the window to being able to run the large library of software which is available for it. What do we need to do to make the memory system compatible?

The majority of the CP/M system itself loads and runs at the top of memory, the highest addresses available. We have plenty of RAM available here, so this is not a problem. But it also needs to load some code into the very lowest memory addresses, starting at address $0000, and it needs to be able to load user programs into memory starting at address $100. We have our ROM situated in the lower 16Kb of memory which creates a problem.

Could we move the ROM elsewhere in the memory map? Unfortunately not. On reset the Z80 starts running code at address $0000 and this cannot be changed. How do we work around this? What if our computer could switch this 16Kb block of memory between ROM and RAM?

If we could do this then we could copy some boot up code from ROM into RAM, turn the ROM off and load CP/M into the RAM which is now in that space? This concept is actually a basic form of memory paging which is often used in systems which have more memory than can be addresses by the processor at one time5.

A memory map with basic paging of the first 16Kb between ROM and RAM
A memory map with basic paging of the first 16Kb between ROM and RAM

What we need is something which can store a ‘flag’ or setting. If the flag is clear then the the first 16Kb of memory reads from ROM, if it is set then this block reads from RAM. And the rest of the address space always reads from RAM, as now.

Let’s begin by looking at the ‘flag’. Here we can use a D-type latch similar to the 74LS273 which we used in the keyboard scanning hardware. I’m actually going to use a 74LS74 ‘Dual D Flip Flop’. Unlike the 74LS273 the 74LS74 only stores a single bit6 of data but that’s all we need here.

74LS74 Dual D-type Flip Flip pinout
74LS74 Dual D-type Flip Flip pinout

The 74LS74 functions by storing the value on the D (data) pin when the CK (clock) pin transitions from low to high. The stored data is output on the Q pin and the inverted data is output on the /Q pin. There are also /CLR (clear) and /SET (set) pins which, as their names imply, clear or set the stored data independently of the clock input.

If we connect the CK (clock) input to one of our I/O enable signals (of the 74LS138 we installed in part 3) and the D (data) input to one of the Z80’s data lines (I’m using D0) then we can set or clear the latch by writing to the appropriate I/O port.7

The 74LS74 gives us the choice of either the Q or /Q outputs (which can be an advantage over chips like the 74LS273). For the rest of my logic here the Q (active low) output is the most convenient. We can utilise it by ORing Q against the output of the A14/A15 OR gate. Thus when the latch is clear this new OR gate passes through the output from the A14/A15 OR gate. When the latch is set the new OR gate always outputs a logic high. This logic high means that, when the latches data is high, the RAM_CS2 (active high) signal will always be high (and the RAM will always be enabled, subject to the other signals) and the /ROM_CS will also always be high and thus the ROM will always be disabled.

And , to finish off, I’m connecting the 74LS74’s /CLR input computers /RESET button which ensures the latch will always be clear when the computer is reset, and thus we will always have the ROM paged in when our computer starts.

Here is the final memory section schematic:

The final schematic for the memory selection circuit with ROM disable latch
The final schematic for the memory selection circuit with ROM disable latch

Wiring Up

The only hardware left to add is the actual memory chip. I’m using an 621024 which I had to hand. You could also use a 628128 as shown on the schematic. They’re both compatible and have the same pinout and are fully interchangeable. They’re also both 128K byte chips. I’m using 128K chips because, as far as I can tell, 64K byte chips are not easily available (if available at all). And memory is so cheap that it there wouldn’t be a significant price difference if one was available. For now we’re only using half of the memory but I may look at ways to access the other 64K in a later article.

The full computer with RAM and bank selection circuitry added.
The full computer with RAM and bank selection circuitry added. The 74LS74 dual latch is position top-left, with the latch on the top side of the chip being used (I’ve wired D0, /RESET and /SET of the other latch ready for a future addition). To the right of that is the 74LS32 OR gates, and then the RAM chip itself. The pink wire running down the left hand side of the board is the I/O port enable line running from the 74LS138.

If you refer to the photos notice that I’ve positioned the RAM chip so that I can directly wire across the Z80’s lower address pins (the lower green wires) and the higher address pins can jump across to the address pins on the other side.

If you compare this to the pinouts of the Z80 and the RAM chip you’ll notice that I’ve wired the address pins out of sequence. This is intentional. I’m wiring so that the address lines can be connected in sequence. As far as the memory is concerned, the only functions it has are to store data at an address and retrieve data from an address and therefore it’s immaterial in what order we connect the address pins. The data to retrieve from any memory address will always be the same data we wrote to that address. (Contrast this with the ROM chip. We need to be able to program the ROM chip externally in an EPROM programmer so the address lines need to be in the correct sequence). In the schematic I’ve used the actual wiring layout used on the board which may be of assistance when connecting up.

I could have done the same with the RAM chips data pins but instead I’ve chosen to sort them into sequence. I’ll be daisy-chaining other devices to the data pins so it’s very useful here to have them in the correct order.

The schematics, pinouts and photos should show you how to wire (and rewire) the control signals. Note that I’m daisy-chaining some of the control signals to reduce the number of wires coming from the Z80, but I’m taking the D0 pin from the Z80 rather than the RAM so that I have a spare breadboard hole to daisy-chain the data lines from the RAM to more devices.

The final schematic for part 5
The final schematic for part 5
Pinout for 621024 and 628128 126Kb x 8 SRAM IC
Pinout for 621024 and 628128 126Kb x 8 SRAM IC
Z80 pinout diagram
Z80 pinout diagram
74LS32 pinout diagram
74LS32 pinout diagram

Coding With Subroutines

If you’ve programmed before then you’ve almost certainly used procedures, functions, subroutines or methods (depending on the language) to break up code into shorter sections and to write code which can be reused. And you’ve probably noticed that I haven’t used anything similar in my code so far. That’s not just me being a poor programmer, it’s because when code calls a subroutine it needs to be able to store a return address so the processor knows where to return to after the end of the subroutine. And that return address is usually stored in RAM. And we didn’t have any RAM.

But now that we have RAM it’s time to start rewriting the code we already have to use subroutines. To this end I’ve broken out (and rewritten) code to access the LCD display into the file CharLCDLib.z80, code to scan a 4×4 or 4×3 keypad into KeypadLib.z80 and code to scan the RC2014 (and compatible) keyboards in KeyboardLib.z80.

The LCD library includes routines to initialise the display, send commands, data and ASCIIZ strings, clear the display, position the cursor etc.

The key scanning libraries both have a single entry point called key_scan and you can ‘include’ whichever library is appropriate for your build.

Subroutines on the Z80

In Z80 assembler you call a subroutine with the CALL instruction. As with the JP and JR instructions there are both unconditional versions and conditional versions which only make the call if the specified flag is set or clear.

The CALL instruction makes use of the Z80’s stack which, in turn, uses the SP (stack pointer) register. When the Z80 makes a call it writes (‘pushes’) the return address (the address of the instruction following the CALL instruction) onto the top of the stack, advances the stack pointer to the next storage location, and loads the PC register with the new address (read from the instruction).

Returning from a subroutine uses the RET (return) instruction. Again there are unconditional and conditional versions. This instruction reads (‘pops’) the address from the top of the stack, moves the stack pointer to point to the the previous memory location, and loads the popped value into the program counter. Execution thus continues at the address following the original CALL instruction.

The Z80 stack grows downwards – meaning that the SP register is decremented with each byte written – and, since Z80 addresses are 16-bits long, each item on the stack is two bytes long. Thus pushing an item on the stack reduces the SP register by two. The stack pointer in the Z80 points to the last item written to the stack.

Also, the SP register in the Z80 needs to be initialised to point to a suitable memory location.

With our new libraries we can write a simple program which writes a hello world style message to the display and then reads key presses from the keyboard and echos them to the display as follows.

;Pt5.1Echo.z80

lcd_command equ $00     ;LCD command I/O port
lcd_data equ $01        ;LCD data I/O port
key_port equ $20        ;Keyboard in and out port
   
org 0
    ld sp,0             ;Initialise stack pointer
    
    call lcd_initialise ;Setup LCD display
    
    ld hl,welcome_message   ;Display welcome message
    call lcd_send_asciiz

main_loop:    
    call key_scan       ;Fetch a key
    jr nc,main_loop
    
    call lcd_send_data
    
    ld bc,$0000         ;Delay loop - prevent multiple keypresses
sleep_loop:
    dec c
    jr nz,sleep_loop
    dec b
    jr nz,sleep_loop
    
    jr main_loop

    
welcome_message:
    db "Memory Bank Test",0

;Libraries
;---------
    
include "CharLCDLib.z80"

include "KeypadLib.z80"
The keypad/echo test using subroutines

Testing ROM paging

So, our code is successfully using subroutines which means that our RAM is working. We now need to test that our system is putting RAM and ROM into the correct 16Kb memory banks as well as testing the ROM disable function.

Testing for RAM versus ROM is easy. We just write some data and then read it back. If the values we read back are the same as we wrote we have RAM at that address8. If the values come back different then we either have ROM (or something else which isn’t RAM). We can toggle the ROM_disable latch and see whether we have ROM or RAM at any given address.

But there’s a catch. If we run this code from ROM then as soon as we disable the ROM our code will be paged out of memory and we’ll be executing whatever junk is in RAM at the same address and our code will almost certainly fail.

How do we get around this? We need to copy some code into RAM outside the paging area, run it, then have it turn the ROM back on before returning to the rest of the ROM code.

Here’s my code to do the actual test – the section which can be copied to RAM. You call it with the desired ROM_disable setting in the A register (0=ROM enabled, 1=ROM disabled) and an address to test in HL. This switches the bank setting, cycles though a number to write/read test values at the given address and returns success of failure via the carry flag.

;Test if the memory at the byte pointed to by HL is working RAM
;In: A=Value for rom_disable_port, HL=Memory address
;Out: Carry set if passed, Carry clear if failed.
;   AF corrupt. All other registers preserved
ram_test_byte: 
    out (rom_disable_port),a
    
    ld a,(hl)           ;Preserve old memory data
    push af
    
    xor a               ;A=0
ram_test_byte_loop:
    ld (hl),a           ;Write data
    cp (hl)             ;Read it back and compare
    jr nz,ram_test_fail ;Different = fail
    dec a               ;Else, next test value and loop
    jr nz,ram_test_byte_loop
    
    ;RAM test passed
    pop af              ;Put the original data back
    ld (hl),a
    xor a               ;Turn ROM back on
    out (rom_disable_port),a
    scf                 ;Set carry
    ret
    
ram_test_fail
    pop af              ;Put the original data back (probably needless!)
    ld (hl),a
    xor a               ;Turn ROM back on
    out (rom_disable_port),a
    and a               ;Clear carry
    ret
    
ram_test_byte_end equ $ ;Get current code address

The $ symbol in the last line of this code creates a label called ram_test_byte_end whose value is the target address of the assembler. I.e. the address at which the next instruction will be assembled at. We’ll use this label later when we copy the code to RAM.

When developing this I made the mistake of calling LCD routines to display the pass or fail status but this crashed because the ROM was already paged out. Therefore we can’t call any code located in ROM.

We also need to bear in mind that when being copied to RAM this code will be running at a different address to that which it was assembled to run at. If we use any calls, absolute jumps or memory reads of data within this code block they will fail. The assembler would create code with absolute memory addresses in ROM, rather than at the new target address.

There are ways to steer the assembler around this, to get it to assemble code at one address but which is designed to run at a different address. And there are ways to create relocateable code where absolute memory addresses can be changed depending on where the code needs executing from. But, since this code is small and simple, it’s easy to write is to only use relative jumps.

Testing Multiple Banks

This next piece of code runs the test once for each 16Kb memory bank. This code outputs the bank index (0 to 3) and the test result – P(ass) or F(ail) – to the LCD. (The code here is outputting strings with a single character (P or F) because the LCD display has so few characters available but this leaves the flexibility to output a more meaningful string on a larger display or via a communication link).

;Test each memory bank to see where we have valid RAM
;Reports a 16Kb memory bank index and P(ass) or (F)ail for each 16K bank.

ram_test:
    ld hl,$1000         ;Initial test address
    push af             ;A=ROM bank setting
    
ram_test_loop:
                        ;Output RAM bank index (bits 15,14 of HL as ASCII digit)
    ld a,h              ;Move bits 7,6 of H to bits 1,0 of A
    rlca
    rlca
    and %00000011       ;Mask out unwanted bits
    add a,'0'           ;Convert to an ASCII digit
    call lcd_send_data

    pop af              ;Retrieve ROM bank setting
    push af
    call ram_test_byte_dest
                        ;Test. Code has been moved into RAM, use correct address
   
    push hl             ;Preserve test address
    
    ld hl,ram_test_pass_msg ;Choose the appropriate message
    jr c,ram_test_output    ;Jump on the result of the ram_test_byte_dest call
    
    ld hl,ram_test_fail_msg
ram_test_output:
    call lcd_send_asciiz    ;Output result message
    
    pop hl              ;Retrieve address
    ld a,h
    add a,$40           ;Next bank
    ld h,a
    jr nc,ram_test_loop ;Loop
    
    pop af              ;Remove ROM bank
    ret       
    
ram_test_pass_msg:
    db "P",0
ram_test_fail_msg:
    db "F",0

and finally we have the code to copy the ram_test_byte code and run the tests once with the rom_disable off and a second time with it on.

;RAM test code
;Does each 16K bank contain ROM or RAM?
;Does the ROM paging hardware work correctly?
;=============
ram_test_byte_dest equ $8000

rom_ram_test:
    ld de,$0001         ;Position cursor on line 2
    call lcd_gotoxy
    
    ld hl,ram_test_byte ;Code to be moved
    ld de,ram_test_byte_dest ;Destination address
    ld bc,ram_test_byte_end - ram_test_byte
                        ;Length of code
    ldir                ;Copy
    
    ld a,0              ;Enable ROM
    call ram_test       ;Test
    
    ld a,1              ;Disable ROM
    call ram_test       ;Test
    
    ret

This code uses one of the Z80s most powerful functions – LDIR – to do the copy operation.

LDIR takes a source address in the HL register pair, a destination address in the DE register pair and a byte count in the BC register pair. It copies a byte from the address pointed to by HL to the address pointed to by DE, increases both HL and DE by one and decreases BC by one. If BC is now other than zero it repeats the operation again, otherwise it terminates and execution continues with the next instruction.

It should be easy to see that this instruction copies a block of memory from one location to another.

Here’s a photo of the output of this code. The second line shows the test results. It begins with the tests of each bank with ROM enabled: note that bank 0 fails. It then repeats with ROM disabled. Now the test of bank 0 passes! And thus we can conclude that the ROM disable latch and the associated hardware is working as intended.

Running to memory bank test program
Running to memory bank test program

Summary

As ever, code, schematics and other resources can be found on the Github repo for the series.

And that’s our memory system finished for now. I hope to return at a future time to look at how we can use the extra 64K of RAM available in the RAM chip, and maybe even the extra 32K or ROM available in the ROM chip. We also have a spare latch on the 74LS74 and a spare OR gate which I think is enough to add another nice feature to our memory system but, for now, that will have to wait for another day.

For me the next most important feature to add is the ability to communicate with another computer. This will allow us to use, for example, a PC to send and receive data which can move us towards running some more interesting software and this is what I’ll be looking at in the next article in this series.

Buying Links

The links below are affiliate links unless stated otherwise.

Footnotes

  1. The Datapoint 2200 also had a TTL processor – a processor made from discrete TTL logic chips – the design of which inspired the design of the Intel 8080, and thus the Z80, as well as the Intel 8086 and thus today’s Pentium processors
  2. Multiplexing means sending multiple signals along a single wire. In this case alternating between the two halves of the address bus.
  3. The two halves of the address are referred to as RAS (Row Address Select) and CAS (Column Address Select). The memory chips had input pins to signal which values were on the address pins.
  4. At the time the Z80 was designed RAM chips only used seven rows so this was sufficient. There are some later versions of the Z80 with an 8-bit refresh counter.
  5. Modern processors also use memory paging to give each process it’s own block of memory separate (and thus protected) from other processes.
  6. The 74LS74 actually has two separate single bit latches on a single chip. I have plans which involve the ‘spare’ latch :)
  7. Since the outputs of the 74LS138 are active low and the clock input of the 74LS74 is active high you may ask whether this circuit will operate correctly. The 74LS74 will latch the data when the ‘138’s output signal is deactivated, which happens when the Z80’s control signals (/IORQ and /M1) are deactivated. The Z80 actually holds the values on the data pins beyond this time for exactly this kind of scenario. In fact, most devices latch the data shortly after the end of the enable and write signals cease.
  8. To be truly sure we need to test multiple data values at a given location, otherwise we could be writing the value which just happens to be the same as that in ROM at that location.

11 Replies to “Couch to 64k Part 5: Adding RAM and a CP/M Compatible Memory Architecture to the Z80 Breadboard Computer”

  1. Hello, thank you for the clear and fascinating articles. Small question: why ld sp, 0 and not ld sp $ffff for example? adress 0 is in rom at this point, then won’t the first item on the stack be ignored? Or, more generally, how to choose the right initialization address for SP? Are there any particular aspects to consider? Thanks in advance.

    1. Hi, SP on the Z80 points to the last item pushed on the stack. When you push the next item SP is decremented and the new item stored (this happens twice, of course, for the two bytes). So when SP is initialised to zero the first items pushed on the stack will be stored at $ffff and $fffe.

  2. I noticed logic chips LS, but it also seemed that HC can be used? Would using HC be ok no nasty side effects 🙂
    Ty so much looking forward to building this.

    1. HC is not fully compatible with LS or HCT. IF you’re using all HC you should be okay. Mixing will *probably* be okay for a hobbyist project like this.

  3. Think you got your RAM active low and active high ports the wrong way around.
    “CS1 which is active high and CS2 which is active low”, it should be CS1 which is active LOW and CS2 which is active HIGH. Unless I’m confusing myself, have looked at that line for ages.

  4. I like your usage of the address lines for the RAM, never thought about it that way. But what goes in, much come out, it doesn’t matter how it’s wired up as long as you don’t use the RAM address lines for anything else.
    Have you thought about using a ZIF socket for the EEPROM, and if so what would you recommend.

    1. The ZIF sockets I’ve seen all have fairly should pins which wouldn’t sit nicely in a breadboard. In any case, the EPROM I’m using is programmable at five volts, so it should be possible to program it from the Z80. I’ve tentatively wired the second flip flop to enable/disable writing to it. I just haven’t gotten around to testing it yet. (And it would need the SDP – Software Data Protection – to be disabled first anyway).

  5. It makes sense not to lose the opportunity to make the ROM flashable. And thanks for the tip on using /RD, it makes it certainly easier to OR with the rest.

  6. Very interesting articles, as nice as Eater videos.
    Would it work to use the RW signal on the Bank selection logic to always force RAM on writes? This was done somehow on the Apple II.
    ROM code could be copied into RAM by reading and writing in place. And there would be no issues with relocation of absolute addresses.

    1. Yes it would. I grew up with an Amstrad CPC which did it. One of the banks of ROM was over the screen RAM so it could write to the screen without having to page out the ROM.

      All you’d need to do is include the /WR signal in the chip selection logic for the RAM so the RAM is always enabled when there’s a memory write happening or (since the Z80 has separate /RD and /WR signals and one or other will be active when accessing memory) use the /RD signal if it makes the logic easier. Since /WE is hard wired off for the ROM then the ROM won’t be affected.

      The chief reason I haven’t done this is because, since I’m using a ROM chip which can be programmed at five volts, I’d like to make the ROM flashable. It would still be possible to send all writes to RAM except when the system allows writing to ROM but the logic starts to get more complicated than I wanted to to into.

Comments are closed.