1
0
mirror of https://github.com/KarolS/millfork.git synced 2024-07-05 09:28:54 +00:00

Z80: Full assembly support

This commit is contained in:
Karol Stasiak 2018-07-24 17:40:06 +02:00
parent 80efa95ba7
commit b724ba9c6a
5 changed files with 665 additions and 23 deletions

View File

@ -21,12 +21,12 @@ case class IfFlagSet(flag: ZFlag.Value) extends ZRegisters
case class IfFlagClear(flag: ZFlag.Value) extends ZRegisters
case class OneRegister(register: ZRegister.Value) extends ZRegisters {
if (register == ZRegister.MEM_IY_D || register == ZRegister.MEM_IX_D) ???
// if (register == ZRegister.MEM_IY_D || register == ZRegister.MEM_IX_D) ???
}
case class TwoRegisters(target: ZRegister.Value, source: ZRegister.Value) extends ZRegisters {
if (target == ZRegister.MEM_IY_D || target == ZRegister.MEM_IX_D) ???
if (source == ZRegister.MEM_IY_D || source == ZRegister.MEM_IX_D) ???
// if (target == ZRegister.MEM_IY_D || target == ZRegister.MEM_IX_D) ???
// if (source == ZRegister.MEM_IY_D || source == ZRegister.MEM_IX_D) ???
}
case class OneRegisterOffset(register: ZRegister.Value, offset: Int) extends ZRegisters {
@ -214,10 +214,10 @@ case class ZLine(opcode: ZOpcode.Value, registers: ZRegisters, parameter: Consta
case ZRegister.I => "I"
case ZRegister.MEM_ABS_8 => s"($parameter)"
case ZRegister.MEM_ABS_16 => s"($parameter)"
case ZRegister.IMM_8 => s"#$parameter"
case ZRegister.IMM_16 => s"#$parameter"
case ZRegister.MEM_IX_D => s"(IX,$offset)"
case ZRegister.MEM_IY_D => s"(IY,$offset)"
case ZRegister.IMM_8 => s"$parameter"
case ZRegister.IMM_16 => s"$parameter"
case ZRegister.MEM_IX_D => s"IX($offset)"
case ZRegister.MEM_IY_D => s"IY($offset)"
case ZRegister.MEM_HL => "(HL)"
case ZRegister.MEM_BC => "(BC)"
case ZRegister.MEM_DE => "(DE)"
@ -236,7 +236,7 @@ case class ZLine(opcode: ZOpcode.Value, registers: ZRegisters, parameter: Consta
case IM => s" IM $parameter"
case EX_AF_AF => " EX AF,AF'"
case EX_SP => registers match {
case OneRegister(r) => s" EX (SP),${asAssemblyString(r)})"
case OneRegister(r) => s" EX (SP),${asAssemblyString(r)}"
case _ => ???
}
case JP | JR | DJNZ | CALL =>
@ -277,7 +277,7 @@ case class ZLine(opcode: ZOpcode.Value, registers: ZRegisters, parameter: Consta
}
s" RES ${ZOpcodeClasses.RES_seq.indexOf(op)},$ps"
case op =>
val os = op.toString//.stripSuffix("_16")
val os = op.toString.stripSuffix("_16")
val ps = registers match {
case NoRegisters => ""
case IfFlagSet(ZFlag.P) => " PO"

View File

@ -86,10 +86,23 @@ class Z80Assembler(program: Program,
case ZLine(ADD_16, TwoRegisters(ZRegister.HL, source), _, _) =>
writeByte(bank, index, 9 + 16 * internalRegisterIndex(source))
index + 1
case ZLine(ADD_16, TwoRegisters(ix@(ZRegister.IX | ZRegister.IY), source@(ZRegister.IX | ZRegister.IY)), _, _)=>
if (ix == source) {
writeByte(bank, index, prefixByte(ix))
writeByte(bank, index + 1, 9 + 16 * internalRegisterIndex(HL))
index + 2
} else {
ErrorReporting.fatal("Cannot assemble " + instr)
index
}
case ZLine(ADD_16, TwoRegisters(ix@(ZRegister.IX | ZRegister.IY), source), _, _) =>
writeByte(bank, index, prefixByte(ix))
writeByte(bank, index + 1, 9 + 16 * internalRegisterIndex(source))
index + 2
case ZLine(ADC_16, TwoRegisters(ZRegister.HL, reg), _, _) =>
writeByte(bank, index, 0xed)
writeByte(bank, index + 1, 0x4a + 0x10 * internalRegisterIndex(reg))
index + 2
case ZLine(SBC_16, TwoRegisters(ZRegister.HL, reg), _, _) =>
writeByte(bank, index, 0xed)
writeByte(bank, index + 1, 0x42 + 0x10 * internalRegisterIndex(reg))
@ -108,6 +121,11 @@ class Z80Assembler(program: Program,
writeByte(bank, index + 1, 0x2a)
writeWord(bank, index + 2, param)
index + 4
case ZLine(LD_16, TwoRegisters(ZRegister.MEM_ABS_16, ix@(ZRegister.IX | ZRegister.IY)), param, _) =>
writeByte(bank, index, prefixByte(ix))
writeByte(bank, index + 1, 0x22)
writeWord(bank, index + 2, param)
index + 4
case ZLine(LD_16, TwoRegisters(ZRegister.HL, ZRegister.MEM_ABS_16), param, _) =>
writeByte(bank, index, 0x2a)
writeWord(bank, index + 1, param)
@ -168,8 +186,33 @@ class Z80Assembler(program: Program,
writeByte(bank, index, 0xcb)
writeByte(bank, index + 1, o.opcode + internalRegisterIndex(reg) * o.multiplier)
index + 2
case ZLine(op, OneRegisterOffset(ix@(ZRegister.MEM_IX_D | ZRegister.MEM_IY_D), offset), _, _) if cbOneRegister.contains(op) =>
val o = cbOneRegister(op)
writeByte(bank, index, prefixByte(ix))
writeByte(bank, index + 1, 0xcb)
writeByte(bank, index + 2, offset)
index + 3
case ZLine(LD, registers, _, _) =>
registers match {
case TwoRegisters(I, A) =>
writeByte(bank, index, 0xed)
writeByte(bank, index + 1, 0x47)
index + 2
case TwoRegisters(A, I) =>
writeByte(bank, index, 0xed)
writeByte(bank, index + 1, 0x57)
index + 2
case TwoRegisters(R, A) =>
writeByte(bank, index, 0xed)
writeByte(bank, index + 1, 0x4f)
index + 2
case TwoRegisters(A, R) =>
writeByte(bank, index, 0xed)
writeByte(bank, index + 1, 0x5f)
index + 2
case TwoRegisters(I | R, _) | TwoRegisters(_, I | R) =>
ErrorReporting.fatal("Cannot assemble " + instr)
index
case TwoRegisters(reg, ZRegister.IMM_8) =>
writeByte(bank, index, 6 + 8 * internalRegisterIndex(reg))
writeByte(bank, index + 1, instr.parameter)
@ -377,6 +420,20 @@ class Z80Assembler(program: Program,
writeByte(bank, index, 0x10)
writeByte(bank, index + 1, AssertByte(param - index - 2))
index + 2
case ZLine(EX_SP, OneRegister(HL), _, _) =>
writeByte(bank, index, 0xe3)
index + 1
case ZLine(EX_SP, OneRegister(IX), _, _) =>
writeByte(bank, index, 0xdd)
writeByte(bank, index + 1, 0xe3)
index + 2
case ZLine(EX_SP, OneRegister(IY), _, _) =>
writeByte(bank, index, 0xfd)
writeByte(bank, index + 1, 0xe3)
index + 2
case ZLine(EX_DE_HL, _, _, _) =>
writeByte(bank, index, 0xeb)
index + 1
case _ =>
ErrorReporting.fatal("Cannot assemble " + instr)
index

View File

@ -61,13 +61,15 @@ case class Z80Parser(filename: String, input: String, currentDirectory: String,
"SP" -> ZRegister.SP, "sp" -> ZRegister.SP,
)
private def param(allowAbsolute: Boolean): P[(ZRegister.Value, Option[Expression])] = asmExpressionWithParens.map {
private def param(allowAbsolute: Boolean, allowRI: Boolean = false): P[(ZRegister.Value, Option[Expression])] = asmExpressionWithParens.map {
case (VariableExpression("R" | "r"), false) if allowRI => (ZRegister.R, None)
case (VariableExpression("I" | "i"), false) if allowRI => (ZRegister.I, None)
case (VariableExpression(r), false) if toRegister.contains(r)=> (toRegister(r), None)
case (VariableExpression("HL" | "hl"), true) => (ZRegister.MEM_HL, None)
case (VariableExpression("BC" | "bc"), true) => (ZRegister.MEM_BC, None)
case (VariableExpression("DE" | "de"), true) => (ZRegister.MEM_DE, None)
case (FunctionCallExpression("IX" | "ix", List(o)), true) => (ZRegister.MEM_IX_D, Some(o))
case (FunctionCallExpression("IY" | "iy", List(o)), true) => (ZRegister.MEM_IY_D, Some(o))
case (FunctionCallExpression("IX" | "ix", List(o)), _) => (ZRegister.MEM_IX_D, Some(o))
case (FunctionCallExpression("IY" | "iy", List(o)), _) => (ZRegister.MEM_IY_D, Some(o))
case (e, true) if allowAbsolute => (ZRegister.MEM_ABS_8, Some(e))
case (e, _) => (ZRegister.IMM_8, Some(e))
}
@ -147,7 +149,7 @@ case class Z80Parser(filename: String, input: String, currentDirectory: String,
case (t, None, s, Some(v)) =>
(op8, TwoRegisters(t, s), None, v)
case (t, None, s, None) =>
(op8, TwoRegisters(t, s), None, zero)
(if (is16Bit(t)) op16 else op8, TwoRegisters(t, s), None, zero)
case _ => ???
}
@ -162,6 +164,7 @@ case class Z80Parser(filename: String, input: String, currentDirectory: String,
opcode: String <- identifier ~/ HWS
tuple4/*: (ZOpcode.Value, ZRegisters, Option[Expression], Expression)*/ <- opcode.toUpperCase(Locale.ROOT) match {
case "RST" => asmExpression.map((RST, NoRegisters, None, _))
case "IM" => asmExpression.map((IM, NoRegisters, None, _))
case "EI" => imm(EI)
case "DI" => imm(DI)
case "HALT" => imm(HALT)
@ -169,9 +172,21 @@ case class Z80Parser(filename: String, input: String, currentDirectory: String,
case "RETN" => imm(RETN)
case "RETI" => imm(RETI)
case "RET" => P(jumpConditionWithoutComma).map((RET, _, None, zero))
case "CALL" => (jumpConditionWithComma~asmExpression).map{case (reg, param) => (CALL, reg, None, param)}
case "JP" => (jumpConditionWithComma~asmExpression).map{case (reg, param) => (JP, reg, None, param)}
case "JR" => (jumpConditionWithComma~asmExpression).map{case (reg, param) => (JR, reg, None, param)}
case "CALL" => (jumpConditionWithComma ~ asmExpression).map { case (reg, param) => (CALL, reg, None, param) }
case "JP" => (jumpConditionWithComma ~ param(allowAbsolute = true)).map {
case (NoRegisters, (ZRegister.MEM_ABS_8, Some(VariableExpression("ix" | "IX")))) =>
(JP, OneRegister(ZRegister.IX), None, zero)
case (NoRegisters, (ZRegister.MEM_ABS_8, Some(VariableExpression("iy" | "IY")))) =>
(JP, OneRegister(ZRegister.IY), None, zero)
case (NoRegisters, (ZRegister.MEM_HL, _)) =>
(JP, OneRegister(ZRegister.HL), None, zero)
case (cond, (ZRegister.MEM_ABS_8 | ZRegister.IMM_8, Some(param))) =>
(JP, cond, None, param)
case _ =>
ErrorReporting.error("Invalid parameters for JP", Some(pos))
(NOP, NoRegisters, None, zero)
}
case "JR" => (jumpConditionWithComma ~ asmExpression).map{case (reg, param) => (JR, reg, None, param)}
case "DJNZ" => asmExpression.map((DJNZ, NoRegisters, None, _))
case "CP" => one8Register(CP)
@ -226,9 +241,10 @@ case class Z80Parser(filename: String, input: String, currentDirectory: String,
case "DAA" => imm(DAA)
case "EXX" => imm(EXX)
case "NOP" => imm(NOP)
case "NEG" => imm(NEG)
case "LDI" => imm(LDI)
case "LDD" => imm(LDD)
case "LDI" => imm(LDI) // TODO: Gameboy has a different LDI
case "LDD" => imm(LDD) // TODO: Gameboy has a different LDD
case "LDIR" => imm(LDIR)
case "LDDR" => imm(LDDR)
case "CPI" => imm(CPI)
@ -245,6 +261,8 @@ case class Z80Parser(filename: String, input: String, currentDirectory: String,
case "OUTDR" => imm(OUTDR)
case "OTIR" => imm(OUTIR)
case "OTDR" => imm(OUTDR)
case "RLD" => imm(RLD)
case "RRD" => imm(RRD)
case "PUSH" => one16Register(PUSH)
case "POP" => one16Register(POP)
@ -275,7 +293,7 @@ case class Z80Parser(filename: String, input: String, currentDirectory: String,
(NOP, NoRegisters, None, zero)
}
}
case "EX" => (asmExpressionWithParens ~ HWS ~ position("comma").map(_ => ()) ~ "," ~/ HWS ~ asmExpressionWithParens).map { p: (Expression, Boolean, (Expression, Boolean)) =>
case "EX" => (asmExpressionWithParens ~ HWS ~ position("comma").map(_ => ()) ~ "," ~/ HWS ~ asmExpressionWithParensOrApostrophe).map { p: (Expression, Boolean, (Expression, Boolean)) =>
p match {
case (VariableExpression("AF" | "af"), false, (VariableExpression("AF" | "af"), true)) =>
(EX_AF_AF, NoRegisters, None, zero)
@ -295,16 +313,16 @@ case class Z80Parser(filename: String, input: String, currentDirectory: String,
}
}
case "LD" => (param(true) ~ HWS ~ position("comma").map(_ => ()) ~ "," ~/ HWS ~ param(true)).map {
case "LD" => (param(allowAbsolute = true, allowRI = true) ~ HWS ~ position("comma").map(_ => ()) ~ "," ~/ HWS ~ param(allowAbsolute = true, allowRI = true)).map {
case (r1, e1, (r2, e2)) => merge(LD, LD_16, skipTargetA = false)((r1, e1, r2, e2))
}
case "ADD" => (param(false) ~ HWS ~ position("comma").map(_ => ()) ~ "," ~/ HWS ~ param(false)).map {
case "ADD" => (param(allowAbsolute = false) ~ HWS ~ position("comma").map(_ => ()) ~ "," ~/ HWS ~ param(allowAbsolute = false)).map {
case (r1, e1, (r2, e2)) => merge(ADD, ADD_16, skipTargetA = true)((r1, e1, r2, e2))
}
case "ADC" => (param(false) ~ HWS ~ position("comma").map(_ => ()) ~ "," ~/ HWS ~ param(false)).map {
case "ADC" => (param(allowAbsolute = false) ~ HWS ~ position("comma").map(_ => ()) ~ "," ~/ HWS ~ param(allowAbsolute = false)).map {
case (r1, e1, (r2, e2)) => merge(ADC, ADC_16, skipTargetA = true)((r1, e1, r2, e2))
}
case "SBC" => (param(false) ~ HWS ~ position("comma").map(_ => ()) ~ "," ~/ HWS ~ param(false)).map {
case "SBC" => (param(allowAbsolute = false) ~ HWS ~ position("comma").map(_ => ()) ~ "," ~/ HWS ~ param(allowAbsolute = false)).map {
case (r1, e1, (r2, e2)) => merge(SBC, SBC_16, skipTargetA = true)((r1, e1, r2, e2))
}

View File

@ -0,0 +1,563 @@
package millfork.test
import millfork.test.emu.EmuUnoptimizedZ80Run
import org.scalatest.{FunSuite, Matchers}
/**
* @author Karol Stasiak
*/
class Z80AssemblySuite extends FunSuite with Matchers {
test("Common I80 instructions") {
EmuUnoptimizedZ80Run(
"""
| asm void main () {
| ret
|
| nop
| ld bc,$101
| ld (bc),a
| inc bc
| inc b
| dec b
| ld b,6
| rlca
| add hl,bc
| ld a,(bc)
| dec bc
| inc c
| dec c
| ld c,$e
| rrca
|
| ld de,$1111
| ld (de),a
| inc de
| inc d
| dec d
| ld d,$16
| rla
| jr main
| add hl,de
| ld a,(de)
| dec de
| inc e
| dec e
| ld e,$1e
| rra
|
| jr nz,main
| ld hl,$2121
| inc hl
| inc h
| dec h
| ld h,$26
| daa
| jr z,main
| add hl,hl
| dec hl
| inc l
| dec l
| ld l,$2e
| cpl
|
| jr nc,main
| ld hl,$2121
| ld ($fffe),a
| inc sp
| inc (hl)
| dec (hl)
| ld h,$26
| scf
| jr c,main
| add hl,sp
| ld a,($fffe)
| dec sp
| inc a
| dec a
| ld l,$2e
| ccf
|
| ld b,b
| ld b,c
| ld b,d
| ld b,e
| ld b,h
| ld b,l
| ld b,(hl)
| ld b,a
|
| ld c,b
| ld c,c
| ld c,d
| ld c,e
| ld c,h
| ld c,l
| ld c,(hl)
| ld c,a
|
| ld d,b
| ld d,c
| ld d,d
| ld d,e
| ld d,h
| ld d,l
| ld d,(hl)
| ld d,a
|
| ld e,b
| ld e,c
| ld e,d
| ld e,e
| ld e,h
| ld e,l
| ld e,(hl)
| ld e,a
|
| ld h,b
| ld h,c
| ld h,d
| ld h,e
| ld h,h
| ld h,l
| ld h,(hl)
| ld h,a
|
| ld l,b
| ld l,c
| ld l,d
| ld l,e
| ld l,h
| ld l,l
| ld l,(hl)
| ld l,a
|
| ld (hl),b
| ld (hl),c
| ld (hl),d
| ld (hl),e
| ld (hl),h
| ld (hl),l
| halt
| ld (hl),a
|
| ld a,b
| ld a,c
| ld a,d
| ld a,e
| ld a,h
| ld a,l
| ld a,(hl)
| ld a,a
|
| add a,b
| add a,c
| add a,d
| add a,e
| add a,h
| add a,l
| add a,(hl)
| add a,a
|
| adc a,b
| adc a,c
| adc a,d
| adc a,e
| adc a,h
| adc a,l
| adc a,(hl)
| adc a,a
|
| sub b
| sub c
| sub d
| sub e
| sub h
| sub l
| sub (hl)
| sub a
|
| sbc a,b
| sbc a,c
| sbc a,d
| sbc a,e
| sbc a,h
| sbc a,l
| sbc a,(hl)
| sbc a,a
|
| and b
| and c
| and d
| and e
| and h
| and l
| and (hl)
| and a
|
| xor b
| xor c
| xor d
| xor e
| xor h
| xor l
| xor (hl)
| xor a
|
| or b
| or c
| or d
| or e
| or h
| or l
| or (hl)
| or a
|
| cp b
| cp c
| cp d
| cp e
| cp h
| cp l
| cp (hl)
| cp a
|
| ret nz
| pop bc
| jp nz,main
| jp main
| call nz,main
| push bc
| add a,1
| rst 0
|
| ret z
| ret
| jp z,main
| call z,main
| call main
| adc a,1
| rst 8
|
| ret nc
| pop de
| jp nc,main
| call nc,main
| push de
| sub 1
| rst $10
|
| ret c
| jp c,main
| call c,main
| sbc a,1
| rst $18
|
| pop hl
| ex (sp),hl
| push hl
| and 1
| rst $20
|
| jp (hl)
| xor 1
| rst $28
|
| pop af
| di
| push af
| or 1
| rst $30
|
| ld sp,hl
| ei
| cp 1
| rst $38
|
| ret
| }
""".stripMargin)
}
test("Intel 8080 instructions") {
EmuUnoptimizedZ80Run(
"""
| asm void main () {
| ret
| ex af,af'
| djnz main
| ld ($fffe),hl
| ld hl,($fffe)
| out (1),a
| exx
| in a,(1)
| ret po
| jp po,main
| call po,main
| ret pe
| jp pe,main
| ex de,hl
| call pe,main
| ret p
| jp p,main
| call p,main
| ret m
| jp m,main
| call m,main
|
| ret
| }
""".stripMargin)
}
test("Extended I80 instructions") {
EmuUnoptimizedZ80Run(
"""
| asm void main () {
| ret
|
| reti
|
| rlc b
| rlc c
| rlc d
| rlc e
| rlc h
| rlc l
| rlc (hl)
| rlc a
|
| rrc b
| rrc c
| rrc d
| rrc e
| rrc h
| rrc l
| rrc (hl)
| rrc a
|
| rl b
| rl c
| rl d
| rl e
| rl h
| rl l
| rl (hl)
| rl a
|
| rr b
| rr c
| rr d
| rr e
| rr h
| rr l
| rr (hl)
| rr a
|
| sla b
| sla c
| sla d
| sla e
| sla h
| sla l
| sla (hl)
| sla a
|
| sra b
| sra c
| sra d
| sra e
| sra h
| sra l
| sra (hl)
| sra a
|
| srl b
| srl c
| srl d
| srl e
| srl h
| srl l
| srl (hl)
| srl a
|
| bit 1,a
| res 1,a
| set 1,a
| bit 1,(hl)
| res 1,(hl)
| set 1,(hl)
|
| ret
| }
""".stripMargin)
}
test("Z80 instructions with IX") {
EmuUnoptimizedZ80Run(
"""
| asm void main () {
| ret
| add a,ix(0)
| adc a,ix(0)
| sub ix(0)
| sbc a,ix(0)
| and ix(0)
| xor ix(0)
| or ix(0)
| cp ix(0)
|
| rrc ix(0)
| rr ix(0)
| rlc ix(0)
| rl ix(0)
| sla ix(0)
| sra ix(0)
| srl ix(0)
| sll ix(0)
|
| pop ix
| push ix
| add ix,sp
| add ix,ix
| add ix,de
| add ix,bc
| inc ix
| dec ix
| ld ix,3
| ld ix,(3)
| ld (3),ix
| ex (sp),ix
| jp (ix)
| ld sp,ix
| ld a,ix(0)
| ld ix(0),a
|
| ret
| }
""".stripMargin)
}
test("Z80 instructions with IY") {
EmuUnoptimizedZ80Run(
"""
| asm void main () {
| ret
| add a,iy(0)
| adc a,iy(0)
| sub iy(0)
| sbc a,iy(0)
| and iy(0)
| xor iy(0)
| or iy(0)
| cp iy(0)
|
| rrc iy(0)
| rr iy(0)
| rlc iy(0)
| rl iy(0)
| sla iy(0)
| sra iy(0)
| srl iy(0)
| sll iy(0)
|
| pop iy
| push iy
| add iy,sp
| add iy,iy
| add iy,de
| add iy,bc
| inc iy
| dec iy
| ld iy,3
| ld iy,(3)
| ld (3),iy
| ex (sp),iy
| jp (iy)
| ld sp,iy
| ld a,iy(0)
| ld iy(0),a
|
| ret
| }
""".stripMargin)
}
test("Other Z80 instructions") {
EmuUnoptimizedZ80Run(
"""
| asm void main () {
| ret
|
| sll b
| sll c
| sll d
| sll e
| sll h
| sll l
| sll (hl)
| sll a
|
| in b,(c)
| out(c),b
| sbc hl,bc
| ld (34),bc
| neg
| retn
| im 0
| ld i,a
| in c,(c)
| out (c),c
| adc hl,bc
| ld bc,(7)
| ld r,a
| in d,(c)
| out (c),d
| sbc hl,de
| ld (55),de
| im 1
| ld a,i
| in e,(c)
| out (c),e
| adc hl,de
| ld de,(33)
| im 2
| ld a,r
|
| in h,(c)
| out (c),h
| sbc hl,hl
| rrd
| in l,(c)
| out (c),l
| adc hl,hl
| rld
| sbc hl,sp
| ld (34),sp
| in a,(c)
| out (c),a
| adc hl,sp
| ld sp,(345)
|
| ldi
| cpi
| ini
| outi
| ldd
| cpd
| ind
| outd
| ldir
| cpir
| inir
| otir
| lddr
| cpdr
| indr
| otdr
|
| ret
| }
""".stripMargin)
}
}

View File

@ -23,6 +23,10 @@ class EmuZ80Run(cpu: millfork.Cpu.Value, nodeOptimizations: List[NodeOptimizatio
private val TooManyCycles: Long = 1000000
def apply(source: String): MemoryBank = {
apply2(source)._2
}
def apply2(source: String): (Timings, MemoryBank) = {
Console.out.flush()
Console.err.flush()