[Haskell-cafe] Assembly EDSL in Haskell

Serguey Zefirov sergueyz at gmail.com
Mon Apr 1 17:42:20 CEST 2013


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.




2013/4/1 C K Kashyap <ckkashyap at 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 = 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
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20130401/16f87165/attachment.htm>


More information about the Haskell-Cafe mailing list