lazyboy-0.2.1.1: An EDSL for programming the Game Boy.

Copyright(c) Rose 2019
LicenseBSD3
Maintainerrose@lain.org.uk
Stabilityexperimental
PortabilityPOSIX
Safe HaskellSafe
LanguageHaskell2010

Lazyboy.Types

Description

This module defines datatypes for the various aspects of the target hardware including registers and instructions.

Synopsis

Documentation

type Lazyboy a = RWS () [Instruction] Integer a Source #

A type alias that defines Lazyboy as a specialization of the RWS monad transformer stack. Reader goes unused, Writer is utilized for an output list of Instructions, and State is merely an integer which counts labels, thus naming them.

execLazyboy :: Lazyboy a -> [Instruction] Source #

Executes an action and returns a list of Instructions.

data Location Source #

A type which represents an address or label.

Constructors

Address Word16 
Name Label 
Instances
Eq Location Source # 
Instance details

Defined in Lazyboy.Types

PrintfArg Location Source # 
Instance details

Defined in Lazyboy.Target.ASM

data Condition Source #

A type representing Condition flags on the hardware.

Constructors

Zero 
NonZero 
Carry 
NoCarry 

data Register8 Source #

Named 8-bit registers.

Constructors

A 
B 
C 
D 
E 
H 
L 
Instances
Eq Register8 Source # 
Instance details

Defined in Lazyboy.Types

Read Register8 Source # 
Instance details

Defined in Lazyboy.Types

Show Register8 Source # 
Instance details

Defined in Lazyboy.Types

PrintfArg Register8 Source # 
Instance details

Defined in Lazyboy.Target.ASM

Comparable Word8 Register8 Source #

An instance for comparing a Word8 and an 8-bit register (this is an alias).

Instance details

Defined in Lazyboy.Control

Comparable Register8 Word8 Source #

An instance for comparing an 8-bit register and a Word8.

Instance details

Defined in Lazyboy.Control

Comparable Register8 Register8 Source #

An instance for comparing two 8-bit registers.

Instance details

Defined in Lazyboy.Control

data Register16 Source #

Named 16-bit registers.

Constructors

BC 
DE 
HL 
AF 
SP 
PC 

data Label Source #

A type which represents a label, which may be local or global in scope.

Constructors

Local Integer 
Global Integer 
Instances
Eq Label Source # 
Instance details

Defined in Lazyboy.Types

Methods

(==) :: Label -> Label -> Bool #

(/=) :: Label -> Label -> Bool #

PrintfArg Label Source # 
Instance details

Defined in Lazyboy.Target.ASM

data Instruction Source #

Type-level representations of instructions and primitive special forms.

Constructors

LDrr Register8 Register8

Load the value in one Register8 into another.

LDrn Register8 Word8

Load the immediate Word8 into a Register8.

LDrHL Register8

Load the Word8 stored at the address in HL into a Register8.

LDHLr Register8

Load the Word8 stored in a Register8 into the address in HL.

LDHLn Word8

Load the immediate Word8 into the address in HL.

LDArr Register16

Load the value at the address contained in a Register16 into A.

LDrrA Register16

Load A into the address contained in a Register16.

LDAnn Location

Load the Word8 stored in the Location into A.

LDnnA Location

Load the Word8 stored in A into the Location.

LDAIO Word8

Read into A from IO port n (FF00 + Word8).

LDIOA Word8

Store the Word8 in A into IO port n (FF00 + Word8).

LDAIOC

Read from IO port FF00+C into A.

LDIOCA

Store the Word8 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 a Location into a Register16.

LDSPHL

Set the stack pointer (SP) to the value in HL.

PUSH Register16

Push Register16 onto the stack.

POP Register16

Pop Register16 from the stack.

JP Location

Immediately and unconditionally jump to a Location.

JPHL

Immediately and unconditionally jump to the value contained in HL.

JPif Condition Location

Conditionally jump to a Location.

CALL Location

Call a Location.

CALLif Condition Location

Conditionally call a Location.

RET

Return from a labelled block.

RETif Condition

Conditionally return from a labelled block.

RETi

Return and enable interrupts.

RST Word8

Call a restart vector.

ADDAr Register8

Add the value contained in a Register8 to A.

ADDAn Word8

Add a Word8 to the value contained in A.

ADDHL

Add the value contained in the address stored in HL to A.

ADCAr Register8

Add the value in a Register8 + the carry flag to A.

ADCAn Word8

Add a Word8 + the carry flag to A.

ADCHL

Add the value pointed to by HL + the carry flag to A.

SUBAr Register8

Subtract the value contained in a Register8 from A.

SUBAn Word8

Subtract a Word8 from A.

SUBHL

Subtract from A the value contained at the address in HL.

SBCAr Register8

Subtract from A the value contained in a Register8 + the carry flag.

SBCAn Word8

Subtract from A a Word8 + the carry flag.

SBCAHL

Subtract from A the value contained in the address in HL + the carry flag.

ANDr Register8

Assign to A the value contained in a Register8 & A itself.

ANDn Word8

Assign to A a Word8 & A itself.

ANDHL

Assign to A itself & the value in the address in HL.

XORr Register8

Assign to A the value contained in a register ^ A itself

XORn Word8

Assign to A a Word8 ^ itself.

XORHL

Assign to A itself ^ the value in the address in HL.

ORr Register8

Assign to A the value contained in a register | A itself.

ORn Word8

Assign to A a Word8 | itself.

ORHL

Assign to A itself | the value in the address in HL

CPr Register8

Subtract from A the value in a Register8 and set flags accordingly, but don't store the result.

CPn Word8

Subtract from A a Word8 and set flags accordingly, but don't store the result.

CPHL

Subtract from A the value in the address in HL, set flags, but don't store the result.

INCr Register8

Increment the value in a Register8.

INCHL

Increment the value at the address in HL.

DECr Register8

Decrement the value in a Register8.

DECHL

Decrement the value at the address in HL.

DAA

Decimal-adjust register A.

CPL

Complement accumulator (A = ~A).

ADDHLrr Register16

Add the value contained in a Register16 to HL.

INCrr Register16

Increment the value in a Register16.

DECrr Register16

Decrement the value in a Register16.

ADDSPn Int8

Add an Int8 to the stack pointer.

LDHLSPn Int8

Load into HL the stack pointer + an Int8.

BITnr Word8 Register8

Test bit n in a Register8, set the zero flag if not set.

BITnHL Word8

Test bit n in the Word8 pointed by HL, set the zero flag if not set.

SETnr Word8 Register8

Set bit n in a Register8.

SETnHL Word8

Set bit n in the Word8 pointed by HL.

RESnr Word8 Register8

Unset bit n in Register8.

RESnHL Word8

Unset bit n in the Word8 pointed by HL.

RLCA

Rotate accumulator left.

RLA

Rotate accumulator left through carry.

RRCA

Rotate accumulator right.

RRA

Rotate accumulator rit through carry.

RLC Register8

Rotate Register8 left.

RLCHL

Rotate value contained at address in HL left.

RL Register8

Rotate Register8 left through carry.

RLHL

Rotate value contained at address in HL left through carry.

RRC Register8

Rotate Register8 right.

RRCHL

Rotate value contained at address in HL right.

RR Register8

Rotate Register8 right through carry.

RRHL

Rotate value contained at address in HL right through carry.

SLA Register8

Shift Register8 left arithmetic.

SLAHL

Shift left arithmetic (HL pointer).

SWAP Register8

Exchange low and high nibbles in Register8.

SWAPHL

Exchange low and high nibbles in HL pointer.

SRA Register8

Shift Register8 right arithmetic.

SRAHL

Shift right arithmetic in HL pointer.

SRL Register8

Shift Register8 right logical.

SRLHL

Shift right logical in HL pointer.

CCF

Complement carry flag.

SCF

Set carry flag.

NOP

No operation.

HALT

Halt until interrupt.

STOP

Standby mode.

DI

Disable interrupts.

EI

Enable interrupts.

LABEL Label

Create a numbered label.

INCLUDE FilePath

Include the file at FilePath.

BYTES [Word8]

Define some bytes in the form of a Word8 list with a global label.

Instances
Eq Instruction Source # 
Instance details

Defined in Lazyboy.Types

Show Instruction Source #

A custom Show instance which formats Instructions as assembly.

Instance details

Defined in Lazyboy.Target.ASM