module Bound.Unwrap ( Fresh
, name
, freshify
, Counter
, UnwrapT
, Unwrap
, runUnwrapT
, runUnwrap
, unwrap
, unwrapAll) where
import Bound
import Control.Monad.Identity
import Control.Applicative
import Control.Monad.Gen
data Fresh a = Fresh { fresh :: !Int
, uname :: a }
deriving (Eq, Ord)
instance Show a => Show (Fresh a) where
show (Fresh i a) = show i ++ '.' : show a
name :: a -> Fresh a
name = Fresh 0
erase :: Fresh a -> a
erase = uname
newtype Counter = Counter {getCounter :: Int}
type UnwrapT = GenT Counter
type Unwrap = Gen Counter
type MonadUnwrap m = MonadGen Counter m
runUnwrapT :: Monad m => UnwrapT m a -> m a
runUnwrapT = runGenTWith (successor $ Counter . succ . getCounter)
(Counter 0)
runUnwrap :: Unwrap a -> a
runUnwrap = runIdentity . runUnwrapT
freshify :: MonadUnwrap m => Fresh a -> m (Fresh a)
freshify nm = (\i -> nm{fresh = i}) <$> fmap getCounter gen
nameF :: MonadUnwrap m => a -> m (Fresh a)
nameF = freshify . name
unwrap :: (Monad f, Functor m, MonadUnwrap m)
=> Fresh a
-> Scope () f (Fresh a)
-> m (Fresh a, f (Fresh a))
unwrap nm s = fmap head <$> unwrapAll nm [s]
unwrapAll :: (Monad f, MonadUnwrap m)
=> Fresh a
-> [Scope () f (Fresh a)]
-> m (Fresh a, [f (Fresh a)])
unwrapAll nm ss = do
fnm <- freshify nm
return $ (fnm, map (instantiate1 $ return fnm) ss)