Skip to content

Commit

Permalink
unified jump instructions around a new location type which can be an …
Browse files Browse the repository at this point in the history
…address or label
  • Loading branch information
ix committed May 7, 2019
1 parent 5db5302 commit a2f85a5
Show file tree
Hide file tree
Showing 8 changed files with 75 additions and 109 deletions.
15 changes: 8 additions & 7 deletions app/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,22 +2,23 @@
module Main where

import Control.Monad
import qualified Data.Text.Lazy.IO as T
import qualified Data.Text.Lazy.IO as T
import Data.Word
import Lazyboy
import Lazyboy.Target.ASM

main :: IO ()
main = rom >>= T.putStrLn
where rom = compileROM $ do
write wram1 0xC0
write (wram1 + 1) 0xDE
write (wram0 + 10) 0xFA
write (wram0 + 11) 0xCE
memcpy wram1 wram0 10
memcpy (wram0 + 10) (wram1 + 10) 10
smiley <- embedBytes image
memcpy (Name smiley) (Address vram) $ fromIntegral $ length image
setBackgroundPalette defaultPalette
setLCDControl $ defaultLCDControl { lcdDisplayEnable = True, lcdBackgroundEnable = True }
freeze

image :: [Word8]
image = [0x00, 0x00, 0x00, 0x00, 0x24, 0x24, 0x00, 0x00, 0x81, 0x81, 0x7e, 0x7e, 0x00, 0x00, 0x00, 0x00]


-- repeat a series of instructions n times
repeatOp :: Int -> Lazyboy () -> Lazyboy ()
Expand Down
43 changes: 0 additions & 43 deletions example/copy.asm

This file was deleted.

4 changes: 4 additions & 0 deletions example/io.asm
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
SECTION "main", ROM0[$0150]

main:
ld HL, main
4 changes: 2 additions & 2 deletions src/Lazyboy/Control.hs
Original file line number Diff line number Diff line change
Expand Up @@ -68,12 +68,12 @@ freeze = loop $ return ()
label <- getLocalLabel
tell [LABEL label]
block
tell [JUMP label]
tell [JP (Name label)]

-- | Executes the given action provided condition flag is set.
cond :: Condition -> Lazyboy () -> Lazyboy ()
cond condition block = do
label <- getLocalLabel
tell [JUMPif condition label]
tell [JPif condition (Name label)]
block
tell [LABEL label]
10 changes: 5 additions & 5 deletions src/Lazyboy/IO.hs
Original file line number Diff line number Diff line change
Expand Up @@ -62,7 +62,7 @@ instance Bitfield LCDControl where
lcdBE = if lcdBackgroundEnable lcds then 0b00000001 else 0

setLCDControl :: LCDControl -> Lazyboy ()
setLCDControl lcd = write lcdc $ pack lcd
setLCDControl lcd = write (Address lcdc) $ pack lcd

-- | A type representing the background palette
data BackgroundPalette = BackgroundPalette { bgpColor3 :: Color
Expand All @@ -83,21 +83,21 @@ instance Bitfield BackgroundPalette where
three = pack bgpColor3 `shiftL` 6

setBackgroundPalette :: BackgroundPalette -> Lazyboy ()
setBackgroundPalette pal = write bgp $ pack pal
setBackgroundPalette pal = write (Address bgp) $ pack pal

-- | Write a byte to a register
byte :: Register8 -> Word8 -> Lazyboy ()
byte reg val = tell [LDrn reg val]

-- | Loads an 8-bit immediate value into a 16-bit memory address
write :: Word16 -> Word8 -> Lazyboy ()
write :: Location -> Word8 -> Lazyboy ()
write addr val = tell [LDrrnn HL addr, LDHLn val]

-- | Copy a region of memory to a destination (up to 255 bytes)
memcpy :: Word16 -> Word16 -> Word8 -> Lazyboy ()
memcpy :: Location -> Location -> Word8 -> Lazyboy ()
memcpy src dest len = do
-- load the destination into DE, source into HL and length into B
tell [LDrrnn HL src, LDrrnn DE dest, LDrn B len]
withLocalLabel $ \label -> do
tell [LDAHLI] -- load a byte from [HL] into A and increment
tell [LDrrA DE, INCrr DE, DECr B, JUMPif NonZero label]
tell [LDrrA DE, INCrr DE, DECr B, JPif NonZero (Name label)]
14 changes: 8 additions & 6 deletions src/Lazyboy/Target/ASM.hs
Original file line number Diff line number Diff line change
Expand Up @@ -40,8 +40,8 @@ instance Show Instruction where
show (LDrrA DE) = printf "ld [DE], A"
show (LDrrA HL) = printf "ld [HL], A"
show (LDrrA r1) = error "A cannot be loaded into 16 bit register '%s'" r1
show (LDAnn v1) = printf "ld A, [$%X]" v1
show (LDnnA v1) = printf "ld [$%X], A" v1
show (LDAnn v1) = printf "ld A, [%s]" v1
show (LDnnA v1) = printf "ld [%s], A" v1
show (LDAIO v1) = printf "ldh A, [$FF00+$%X]" v1
show (LDIOA v1) = printf "ldh [$FF00+$%X], A" v1
show (LDAIOC) = printf "ldh A, [$FF00+C]"
Expand All @@ -52,7 +52,7 @@ instance Show Instruction where
-- handle some special cases for ld rr,nn
show (LDrrnn AF _) = error "You cannot load a 16 bit value directly into the register AF"
show (LDrrnn PC _) = error "You cannot load a 16 bit value directly into the program counter"
show (LDrrnn r1 v1) = printf "ld %s, $%X" r1 v1
show (LDrrnn r1 v1) = printf "ld %s, %s" r1 v1

show (LDSPHL) = printf "%ld SP, HL"

Expand All @@ -66,7 +66,7 @@ instance Show Instruction where
show (POP r1) = printf "POP %s" r1

-- jumps
show (JPnn v1) = printf "jp $%X" v1
show (JP v1) = printf "jp $%X" v1
show (JPHL) = printf "jp HL"
show (JPif c v1) = printf "jp %s, $%X" c v1
show (JRPC v1) = printf "jr %d" v1
Expand Down Expand Up @@ -190,8 +190,6 @@ instance Show Instruction where

-- RGBASM specific stuff
show (LABEL l) = printf "%s:" l
show (JUMP l) = printf "jp %s" l
show (JUMPif c l) = printf "jp %s, %s" c l
show (INCLUDE file) = printf "INCBIN \"%s\"" file
show (BYTES bytes) = printf "db " ++ intercalate "," (map (printf "$%X") bytes)

Expand All @@ -214,6 +212,10 @@ instance PrintfArg Label where
formatArg (Local v) = formatString $ ".L" ++ show v
formatArg (Global v) = formatString $ "L" ++ show v

instance PrintfArg Location where
formatArg (Address v) = formatString $ (printf "$%X" v :: String)
formatArg (Name label) = formatString $ (printf "%s" label :: String)

compileROM :: Lazyboy a -> IO Text
compileROM code = do
templatePath <- getDataFileName "templates/bare.mustache"
Expand Down
72 changes: 37 additions & 35 deletions src/Lazyboy/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -26,6 +26,10 @@ type Lazyboy a = RWS () [Instruction] Integer a
execLazyboy :: Lazyboy a -> [Instruction]
execLazyboy m = snd $ execRWS m () 1

-- | An address or label
data Location = Address Word16 | Name Label
deriving (Read, Show, Eq)

-- | Condition codes
data Condition = Zero | NonZero | Carry | NoCarry
deriving (Read, Show, Eq)
Expand All @@ -43,41 +47,41 @@ data Label = Local Integer | Global Integer

-- | GB Opcodes and other special forms
data Instruction =
LDrr Register8 Register8 -- load the value in one register8 into another
| LDrn Register8 Word8 -- load the immediate value8 into a register8
| LDrHL Register8 -- load the value8 stored at the address in HL into a register8
| LDHLr Register8 -- load the value8 stored in a register8 into the address in HL
| LDHLn Word8 -- load the immediate value8 into the address in HL
| LDArr Register16 -- load the value at the address contained in a 16 bit register into A
| LDrrA Register16 -- laod A into the address contained in a 16 bit register
| LDAnn Word16 -- load the value8 stored in the value16 address into A
| LDnnA Word16 -- load the value8 stored in A into the value16 address
| LDAIO Word8 -- read into A from IO port n (FF00 + value8)
| LDIOA Word8 -- store value8 in A into IO port n (FF00 + value8)
| LDAIOC -- read from IO port FF00+c into A
| LDIOCA -- store the value8 in A into IO port FF00+C
| LDHLAI -- store value in register A into byte pointed by HL and post-increment HL
| LDAHLI -- store value in address in HL in A and post-increment HL
| LDHLAD -- store value in register A into byte pointed by HL and post-decrement HL.
| LDAHLD -- store value in address in HL in A and post-decrement HL
| LDrrnn Register16 Word16 -- load the value16 address into the register16
| LDSPHL -- set the stack pointer to the value in HL
| PUSH Register16 -- push register16 onto the stack
| POP Register16 -- pop register16 from the stack
LDrr Register8 Register8 -- load the value in one register8 into another
| LDrn Register8 Word8 -- load the immediate value8 into a register8
| LDrHL Register8 -- load the value8 stored at the address in HL into a register8
| LDHLr Register8 -- load the value8 stored in a register8 into the address in HL
| LDHLn Word8 -- load the immediate value8 into the address in HL
| LDArr Register16 -- load the value at the address contained in a 16 bit register into A
| LDrrA Register16 -- laod A into the address contained in a 16 bit register
| LDAnn Location -- load the value8 stored in the value16 address into A
| LDnnA Location -- load the value8 stored in A into the value16 address
| LDAIO Word8 -- read into A from IO port n (FF00 + value8)
| LDIOA Word8 -- store value8 in A into IO port n (FF00 + value8)
| LDAIOC -- read from IO port FF00+c into A
| LDIOCA -- store the value8 in A into IO port FF00+C
| LDHLAI -- store value in register A into byte pointed by HL and post-increment HL
| LDAHLI -- store value in address in HL in A and post-increment HL
| LDHLAD -- store value in register A into byte pointed by HL and post-decrement HL.
| LDAHLD -- store value in address in HL in A and post-decrement HL
| LDrrnn Register16 Location -- load the value16 address into the register16
| LDSPHL -- set the stack pointer to the value in HL
| PUSH Register16 -- push register16 onto the stack
| POP Register16 -- pop register16 from the stack

-- Jump & Call instructions
| JPnn Word16 -- immediately jump to value16
| JPHL -- immediately jump to the value contained in HL
| JPif Condition Word16 -- conditional jump to value16
| JRPC Int8 -- relative jump by adding signed value8 to program counter
| JRPCif Condition Int8 -- conditional jump to signed value8 + PC
| CALL Word16 -- call the address
| CALLif Condition Word16 -- conditional call to address
| RET -- return
| RETif Condition -- conditional return
| RETi -- return and enable interrupts
| RST Word8 -- call a restart vector

| JP Location -- immediately jump to value16
| JPHL -- immediately jump to the value contained in HL
| JPif Condition Location -- conditional jump to value16
| JRPC Int8 -- relative jump by adding signed value8 to program counter
| JRPCif Condition Int8 -- conditional jump to signed value8 + PC
| CALL Location -- call the address
| CALLif Condition Location -- conditional call to address
| RET -- return
| RETif Condition -- conditional return
| RETi -- return and enable interrupts
| RST Word8 -- call a restart vector
-- Arithmetic & Logical instructions
| ADDAr Register8 -- add the value contained in a register to A
| ADDAn Word8 -- add a value8 to the value contained in A
Expand Down Expand Up @@ -157,8 +161,6 @@ data Instruction =
-- RGBASM-specific convenience stuff.
-- these would need revamping if we were to start generating native machine code
| LABEL Label -- create a numbered label
| JUMP Label -- jump to a label
| JUMPif Condition Label -- conditional jumping to a label
| INCLUDE FilePath -- include a file
| BYTES [Word8] -- define some bytes with a global label

Expand Down
22 changes: 11 additions & 11 deletions test/Spec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -38,34 +38,34 @@ main = hspec $ do
describe "Lazyboy.Types.execLazyboy" $ do
it "compiles nested sequences in order" $ do
let sequence = execLazyboy $ do
write 0x2000 0x97
write 0x1000 0x98
sequence `shouldBe` [LDrrnn HL 0x2000, LDHLn 0x97, LDrrnn HL 0x1000, LDHLn 0x98]
write (Address 0x2000) 0x97
write (Address 0x1000) 0x98
sequence `shouldBe` [LDrrnn HL (Address 0x2000), LDHLn 0x97, LDrrnn HL (Address 0x1000), LDHLn 0x98]

describe "Lazyboy.Control" $ do
describe "cond" $ do
it "correctly implements conditionals" $ do
let program = execLazyboy $ do
cond NonZero $ do
freeze
program `shouldBe` [JUMPif NonZero $ Local 1, LABEL $ Local 2, JUMP $ Local 2, LABEL $ Local 1]
program `shouldBe` [JPif NonZero $ Name $ Local 1, LABEL $ Local 2, JP $ Name $ Local 2, LABEL $ Local 1]
it "handles nested conditionals correctly" $ do
let program = execLazyboy $ do
cond Zero $ do
cond NonZero $ do
freeze
program `shouldBe` [ JUMPif Zero $ Local 1
, JUMPif NonZero $ Local 2
program `shouldBe` [ JPif Zero $ Name $ Local 1
, JPif NonZero $ Name $ Local 2
, LABEL $ Local 3
, JUMP $ Local 3
, JP $ Name $ Local 3
, LABEL $ Local 2
, LABEL $ Local 1
]
describe "withLabel" $ do
it "creates an appropriately formatted global label" $ do
let program = map show $ execLazyboy $ do
withLabel $ \label -> do
write 0xC000 0x97
write (Address 0xC000) 0x97
program `shouldBe` [ "L1:"
, "ld HL, $C000"
, "ld [HL], 151"
Expand All @@ -74,7 +74,7 @@ main = hspec $ do
it "creates an appropriately formatted local label" $ do
let program = map show $ execLazyboy $ do
withLocalLabel $ \label -> do
write 0xC000 0x97
write (Address 0xC000) 0x97
program `shouldBe` [ ".L1:"
, "ld HL, $C000"
, "ld [HL], 151"
Expand Down Expand Up @@ -103,9 +103,9 @@ main = hspec $ do
it "disallows loading A into [PC]" $ do
disallow (show $ LDrrA PC)
it "disallows loading a 16 bit value into AF" $ do
disallow (show $ LDrrnn AF 0x00)
disallow $ show $ LDrrnn AF $ Address 0x00
it "disallows loading a 16 bit value into PC" $ do
disallow (show $ LDrrnn PC 0x00)
disallow $ show $ LDrrnn PC $ Address 0x00
it "disallows pushing stack pointer" $ do
disallow (show $ PUSH SP)
it "disallows pushing program counter" $ do
Expand Down

0 comments on commit a2f85a5

Please sign in to comment.