
Hello, I'm making an assembly language DSEL in Haskell (just for fun) very similar to the one from Russel O' Conner in [1] I'm trying to specify a 'mov' instruction. A 'mov' instruction has two operands: a destination and a source. There are various constraints on the operands. They have to be of the same size (8-, 16- or 32-bit) and they have to be in a specific format: mov reg reg mov reg mem mov mem reg mov reg imm mov mem imm where reg, mem and imm are register, memmory and immediate values respectively. I would like the type system to check as many constraints as possible. I've managed to get the size constraints working. See the source below this mail. For example the following are all type-correct: valid1 = mov EAX EBX valid2 = mov BX DX valid3 = mov AH AL And the following doesn't pass the type checker: invalid1 = mov EAX BX -- Couldn't match expected type `Bit16' against inferred type `Bit32' I would also like to get the formatting constraints working. However the solution in the code below gives a "Duplicate instance declarations" error. If I -fallow-overlapping-instances than the type checker goes into an infinite loop. I would like to know why this is happening and if there's a way to fix it. Thanks in advance, Bas van Dijk [1] The Monad.Reader Issue 6, Russel O' Conner, Assembly: Circular Programming with Recursive do, http://haskell.org/sitewiki/images/1/14/TMR-Issue6.pdf \begin{code} {-# OPTIONS_GHC -fglasgow-exts -fallow-undecidable-instances #-} module ASM where import Data.Word -- TODO: Not finished yet... -- This is the type of instructions. -- It's going to be a Monad like the one from Russel O'Conner: data AsmM = AsmM deriving Show -- Sizes of registers, memmory or immediate values data Bit32 data Bit16 data Bit8 -- A type-level function that determines the size of a value class Size x size | x -> size -- Types of values class Reg reg class Mem mem class Imm imm -- General Purpose Registers -- Accumulator data EAX = EAX; instance Reg EAX; instance Size EAX Bit32 data AX = AX; instance Reg AX; instance Size AX Bit16 data AH = AH; instance Reg AH; instance Size AH Bit8 data AL = AL; instance Reg AL; instance Size AL Bit8 -- Base data EBX = EBX; instance Reg EBX; instance Size EBX Bit32 data BX = BX; instance Reg BX; instance Size BX Bit16 data BH = BH; instance Reg BH; instance Size BH Bit8 data BL = BL; instance Reg BL; instance Size BL Bit8 -- Counter data ECX = ECX; instance Reg ECX; instance Size ECX Bit32 data CX = CX; instance Reg CX; instance Size CX Bit16 data CH = CH; instance Reg CH; instance Size CH Bit8 data CL = CL; instance Reg CL; instance Size CL Bit8 -- Data data EDX = EDX; instance Reg EDX; instance Size EDX Bit32 data DX = DX; instance Reg DX; instance Size DX Bit16 data DH = DH; instance Reg DH; instance Size DH Bit8 data DL = DL; instance Reg DL; instance Size DL Bit8 -- Memmory data Mem32 = Mem32 Word32; instance Mem Mem32; instance Size Mem32 Bit32 data Mem16 = Mem16 Word32; instance Mem Mem16; instance Size Mem16 Bit16 -- Instructions class Mov dest src where mov :: dest -> src -> AsmM instance ( Size dest size , Size src size , MovFormat dest src ) => Mov dest src where mov d s = AsmM -- TODO: Not finished yet... class MovFormat dest src -- If I have more than one MovFormat instance than I get a -- "Duplicate instance declaration" error: instance (Reg dest, Reg src) => MovFormat dest src instance (Reg dest, Mem src) => MovFormat dest src instance (Mem dest, Reg src) => MovFormat dest src instance (Mem dest, Imm src) => MovFormat dest src instance (Reg dest, Imm src) => MovFormat dest src -- Tests valid1 = mov EAX EBX valid2 = mov BX DX valid3 = mov AH AL -- invalid1 = mov EAX BX -- Couldn't match expected type `Bit16' against inferred type `Bit32' -- invalid2 = mov EAX (Mem32 0) -- No instance for (Reg Mem32) \end{code}