-- | Globally Unique IDentifiers.
module Data.CQRS.GUID
       ( GUID
       , fromByteString
       , newGUID
       , nil
       , toByteString
       ) where

import           Data.ByteString (ByteString)
import qualified Data.ByteString as B
import           Data.ByteString.Char8 ()
import           Data.Typeable (Typeable)
import           Data.Word (Word8)
import           System.Random (randomRIO)

-- | A GUID for values of type 'a'.
newtype GUID a = GUID ByteString
              deriving (Show, Typeable, Eq)

-- | The "nil" GUID. This is used for the root
-- aggregate root which all other aggregate roots
-- can be reached from.
nil :: GUID a
nil = 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 a)
newGUID = do
  uuid <- sequence $ replicate 32 randomWord8
  return $ GUID $ B.pack uuid

-- | Convert GUID to ByteString.
toByteString :: GUID a -> ByteString
toByteString (GUID s) = s

-- | Convert ByteString to GUID.
fromByteString :: ByteString -> GUID a
fromByteString s = GUID s