{-| Module : Graphics.Autom.Rule Description : Helper functions for working with rules Copyright : (c) Christopher Howard, 2016 License : GPL-3 Maintainer : ch.howard@zoho.com These helper functions can be useful when choosing rule values. -} module Graphics.Autom.Rule where import Prelude (($), flip, fromIntegral) import Data.Word (Word8, Word32) import Data.Bits ((.&.), shift, (.|.)) -- |Concatenates four 8-bit values. fromQuad :: Word8 -> Word8 -> Word8 -> Word8 -> Word32 fromQuad n3 n2 n1 n0 = n3' .|. n2' .|. n1' .|. n0' where n3' = shift (fromIntegral n3 :: Word32) 24 n2' = shift (fromIntegral n2 :: Word32) 16 n1' = shift (fromIntegral n1 :: Word32) 8 n0' = fromIntegral n0 :: Word32 -- |Splits a 32-bit value into four 8-bit values. toQuad :: Word32 -> (Word8, (Word8, (Word8, Word8))) toQuad x = (y3, (y2, (y1, y0))) where y3 = fromIntegral $ flip shift (-24) (x .&. 0xFF000000) y2 = fromIntegral $ flip shift (-16) (x .&. 0xFF0000) y1 = fromIntegral $ flip shift (-8) (x .&. 0xFF00) y0 = fromIntegral $ x .&. 0xFF