Skip to content

Instantly share code, notes, and snippets.

@amtal
Created December 27, 2010 03:42
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save amtal/755837 to your computer and use it in GitHub Desktop.
Save amtal/755837 to your computer and use it in GitHub Desktop.
{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies #-}
import Data.Vector as V
import Data.Word
import Data.Bits
data Instr = Seed Word32
| Mutate Word32
| JmpFwd Word16
| JmpRev Word16
| JmpMut Word16
deriving(Eq,Show)
decode :: Vector Word32 -> Vector Instr
decode = V.imap op where
op 0 n = Seed n
op _ n | testBit n 32 = Mutate n
| otherwise = let code = low (low n)
in jmp code (high n)
jmp :: Word8 -> (Word16 -> Instr)
jmp 0 = JmpFwd
jmp 1 = JmpRev
jmp 3 = JmpMut
jmp _ = error "bad jump opcode"
compute :: Vector Instr -> Word32
compute = run 0 0 where
run key pos vec = case vec V.!? pos of
Nothing -> key
Just instr -> let (dx,key') = eval key instr
in run key' (pos+coerce dx) vec
eval :: Word32 -> Instr -> (Word16,Word32)
eval _ (Seed n) = (1, n)
eval key (Mutate n) = (1, key + n)
eval key (JmpFwd j) = (j, key)
eval key (JmpRev j) = ((-j), key)
eval key (JmpMut n) = ( 0 `pack` (high (high key))
, key `xor` (0 `pack` n)
)
-- Utility class for working across sizes.
class Composite a b | a->b where
low :: a -> b
high :: a -> b
pack :: b -> b -> a
coerce :: (Integral a, Num b) => a -> b
coerce = fromIntegral
instance Composite Word32 Word16 where
low = coerce . (.&. 0xFFFF)
high = low . (`shiftR` 16)
pack a b = shiftL 16 (coerce a) .|. coerce b
instance Composite Word16 Word8 where
low = coerce . (.&. 0xFF)
high = low . (`shiftR` 8)
pack a b = shiftL 8 (coerce a) .|. coerce b
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment