You have fixed the type of list by move RAX RAX. Now it has type Instruction SNDREG SNDREG
Make your Instruction a GADT and require that MOV should have appropriate constraints:
{-# LANGUAGE DatatypeContexts, GADTs #-}
data SREG = RIP
data DREG = RBX
data SNDREG = RAX
data Instruction where
MOV :: (Source s, Destination d) => s -> d -> Instruction
class Source a
class Destination a
instance Source SREG
instance Source SNDREG
instance Destination DREG
instance Destination SNDREG
move :: (Source s, Destination d) => s -> d -> Instruction
move s d = MOV s d
hello = [move RAX RAX, move RAX RAX]
hello2 = [move RAX RAX, move RAX RBX] -- this is still not allowed.