module Tip.Fresh where
import Tip.Utils
import Tip.Pretty
import Control.Applicative hiding (empty)
import Control.Monad.State.Strict
import Control.Arrow ((&&&))
import Data.Foldable (Foldable)
newtype Fresh a = Fresh (State Int a)
deriving (Monad, Applicative, Functor, MonadFix)
freshPass :: (Foldable f,Name a) => (f a -> Fresh b) -> f a -> b
f `freshPass` x = f x `freshFrom` x
freshFrom :: (Foldable f,Name b) => Fresh a -> f b -> a
freshFrom m x = runFreshFrom (succ (maximumOn getUnique x)) m
runFresh :: Fresh a -> a
runFresh (Fresh m) = evalState m 0
runFreshFrom :: Int -> Fresh a -> a
runFreshFrom n (Fresh m) = evalState m (n+1)
class (PrettyVar a, Ord a) => Name a where
fresh :: Fresh a
refresh :: a -> Fresh a
refresh _ = fresh
freshNamed :: String -> Fresh a
freshNamed _ = fresh
refreshNamed :: String -> a -> Fresh a
refreshNamed s n = freshNamed (s ++ varStr n)
getUnique :: a -> Int
instance Name Int where
fresh = Fresh (state (id &&& succ))
getUnique = id
instance Name a => Name (PPVar a) where
fresh = fmap PPVar fresh
refresh = fmap PPVar . refresh . unPPVar
freshNamed = fmap PPVar . freshNamed
refreshNamed s n = fmap PPVar (refreshNamed s (unPPVar n))