[Haskell-cafe] A curios monad
Ryan Ingram
ryani.spam at gmail.com
Sat Dec 13 14:47:29 EST 2008
2008/12/11 Luke Palmer <lrpalmer at gmail.com>:
> If you could guarantee that the ID of a key is globally unique, even through
> different invocations of the monad (using eg. unsafePerformIO newUnique),
> then you could ensure type safety and allow transport of keys between
> different monads.
Well, for type-safety you don't need the entire ID of the key; you
just need a globally unique type tag. This is, of course, what
Data.Typeable provides. But you can also roll your own using Uniques:
newtype TKey a = TKey Unique deriving Eq
newTKey :: IO (TKey a)
newTKey = fmap TKey newUnique
castTKey :: TKey a -> TKey b -> Maybe (a -> b)
castTKey (TKey u1) (TKey u2)
| u1 == u2 = Just unsafeCoerce
| otherwise = Nothing
data Key a = Key Int (TKey a) deriving (Eq, Ord)
data StoredValue = forall a. Stored (TKey a) a
type StorageMap = IntMap StoredValue
You then split up the program; one part generates TKeys for the types
in IO; then you can use those throughout the pure rest of the program
to index the types:
newKey :: TKey a -> Storage (Key a)
newKey ta = do
ik <- getNextFreeInt
return $ Key ik ta
-- using MaybeT:
-- newtype MaybeT m a = MaybeT { runMaybeT :: m (Maybe a) }
-- with the appropriate Monad instance
readKey :: Key a -> Storage (Maybe a)
readKey (Key i t) = runMaybeT $ do
Stored tx x <- MaybeT $ lookupMap i
f <- MaybeT $ return (castTKey tx t)
return (f x)
-- exercises for the reader
lookupMap :: Int -> Storage StoredValue
getNextFreeInt :: Storage Int
writeKey :: a -> Key a -> Storage ()
If you're willing to be *slightly* non-referentially transparent, you
can generate the type keys at global scope:
intTKey :: TKey Int
intTKey = unsafePerformIO newTKey
{-# NOINLINE intTKey #-}
(There have been many arguments about "top level IO actions"; I don't
want to get into that here!)
-- ryan
More information about the Haskell-Cafe
mailing list