-- | Globally Unique IDentifiers. module Data.CQRS.GUID ( GUID , fromByteString , hexDecode , hexEncode , newGUID , toByteString ) where import Control.Monad (liftM) import Data.ByteString (ByteString) import qualified Data.ByteString as B import qualified Data.ByteString.Base16 as B16 import Data.ByteString.Char8 () import Data.Default (Default(..)) import Data.Serialize (Serialize(..)) import Data.Typeable (Typeable) import Data.Word (Word8) import System.Random (randomRIO) -- | A Globally Unique IDentifier. newtype GUID = GUID ByteString deriving (Show, Typeable, Eq, Ord) -- | Default GUID value. instance Default GUID where def = GUID $ B.pack $ replicate 32 0 -- | Get a random byte. randomWord8 :: IO Word8 randomWord8 = fmap fromInteger $ randomRIO (0,255) -- | Create a new random GUID. newGUID :: IO GUID newGUID = do uuid <- sequence $ replicate 32 randomWord8 return $ GUID $ B.pack uuid -- | Serialize instance. instance Serialize GUID where put = put . toByteString get = liftM fromByteString get -- | Hex encode a GUID. hexEncode :: GUID -> ByteString hexEncode (GUID s) = B16.encode s -- | Decode a GUID from hex representation. hexDecode :: ByteString -> Maybe GUID hexDecode s = case B16.decode s of (a,b) | B.length b == 0 -> Just $ GUID a _ -> Nothing -- | Convert from ByteString. fromByteString :: ByteString -> GUID fromByteString = GUID -- | Convert to ByteString. toByteString :: GUID -> ByteString toByteString (GUID g) = g