[Haskell-cafe] Assembly EDSL in Haskell
C K Kashyap
ckkashyap at gmail.com
Mon Apr 1 16:09:19 CEST 2013
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 = RIP
data DREG = RBX
data SNDREG = RAX
data (Source s, Destination d) => Instruction s d = MOV s d
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 s d
move s d = MOV s d
hello = [move RAX RAX, move RAX RAX]
hello = [move RAX RAX, move RAX RBX] -- this is still not allowed.
Regards,
Kashyap
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20130401/88aea1c6/attachment.htm>
More information about the Haskell-Cafe
mailing list