------------------------------------------------------------------------
-- |
-- Module      :  ALife.Creatur.Namer
-- Copyright   :  (c) Amy de Buitléir 2012-2013
-- License     :  BSD-style
-- Maintainer  :  amy@nualeargais.ie
-- Stability   :  experimental
-- Portability :  portable
--
-- Assigns a unique ID upon request. IDs generated by an @Namer@ 
-- are guaranteed to be unique within a given universe, across all 
-- simulation runs.
--
------------------------------------------------------------------------
module ALife.Creatur.Namer
  (
    Namer(..),
    SimpleNamer,
    mkSimpleNamer
  ) where

import ALife.Creatur.Counter (PersistentCounter, current, increment,
  mkPersistentCounter)
import ALife.Creatur.Util (stateMap)
import Control.Monad.State (StateT, get, gets)

class Namer n where
  -- | Assign a unique ID using the supplied prefix.
  genName :: StateT n IO String

data SimpleNamer = SimpleNamer 
  {
    prefix :: String,
    counter :: PersistentCounter
  } deriving (Show, Eq)

mkSimpleNamer :: String -> FilePath -> SimpleNamer
mkSimpleNamer s f = SimpleNamer s $ mkPersistentCounter f

withCounter :: StateT PersistentCounter IO x -> StateT SimpleNamer IO x
withCounter runProgram = do
  u <- get
  stateMap (\c -> u {counter=c}) counter runProgram

instance Namer SimpleNamer where
  genName = do
    p <- gets prefix
    k <- withCounter (increment >> current)
    return $ p ++ show k