You have fixed the type of list by move RAX RAX. Now it has type Instruction SNDREG SNDREGMake your Instruction a GADT and require that MOV should have appropriate constraints:
{-# LANGUAGE DatatypeContexts, GADTs #-}data Instruction where
data SREG = RIP
data DREG = RBX
data SNDREG = RAX
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 -> Instructionmove s d = MOV s dhello2 = [move RAX RAX, move RAX RBX] -- this is still not allowed.
hello = [move RAX RAX, move RAX RAX]2013/4/1 C K Kashyap <ckkashyap@gmail.com>
_______________________________________________Hi Cafe,I am trying to embed x86 assembly in Haskell. I'd like the EDSL to not allow invalid movements into registers - for example, should not allow moving into RIP. I was not able to get it to work. I ended up using DataTypeContexts - which is considered misfeature anyway. I was wondering if I could get some suggestions.{-# LANGUAGE DatatypeContexts #-}data SREG = RIPdata DREG = RBXdata SNDREG = RAXdata (Source s, Destination d) => Instruction s d = MOV s dclass Source aclass Destination ainstance Source SREGinstance Source SNDREGinstance Destination DREGinstance Destination SNDREGmove :: (Source s, Destination d) => s -> d -> Instruction s dmove s d = MOV s dhello = [move RAX RAX, move RAX RAX]hello = [move RAX RAX, move RAX RBX] -- this is still not allowed.Regards,Kashyap
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe