
Hi. No, it is not a practical question, I am just curious.. The idea
of my code example was to upgrade "normal" non-reentrant spinlock with
a lock function which helps user to avoid re-locking in same thread.
By the way, looks like I didn't express it correctly. lock function
should actually be named withLock and it's use pattern will be
main = do
withLock sl $ do
liftIO $ putStrLn "sl is locked now, we are in spinlock monad"
withLock sl2 $ do
liftIO $ putStrLn "sl2 is locked now, we are in spinlock monad"
in other words, what I want is to place some kind of mark on a
typelevel saying that lock is being held.
Thanks,
Sergey
2013/5/31 Michael Peternell
maybe you just want to use a recursive lock?
http://en.wikipedia.org/wiki/Reentrant_mutex
The approach you describe will not work, even if you would find a way to use negations on a typelevel. Just find a realistic example of how you would use such a mutex and you will see... It's not possible to know at compile time which call to lock() is the first and which call to lock is a subsequent call on the same thread. If it were, there would be no need to use recursive locking in the first place.
Am 30.05.2013 um 22:05 schrieb Sergey Mironov
: Hi, cafe. Imagine that we are writing an operating system FooOS which uses spinlocks (mutexes, critical sections) to guard shared resources and we want the typesystem to prevent application from re-locking the spinlock which have already been locked by the current thread. Below is the code which does it by explicitly defining MonadSpinlockLess class. Unfortunately, it requires tons of boilerplate instances because we need _any_ monad except SpinlockT to be an instance of MonadSpinlockLess. Is there a better way of doing it? Maybe GADTs?
Basically, it would be sufficient to rewrite lock function as
lock :: (! MonadSpinlock m) => Spinlock -> SpinlockT m a -> m a
but afaik we can't use negations on a typelevel, can we?
Thanks, Sergey
---
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
import Data.IORef
newtype Spinlock = SL (IORef Int)
newtype SpinlockT m a = SpinlockT { unSpinlock :: m a } deriving(Monad)
class (Monad m) => MonadSpinlockLess m instance MonadSpinlockLess IO instance MonadSpinlockLess m => MonadSpinlockLess (ReaderT r m) instance MonadSpinlockLess m => MonadSpinlockLess (WriterT r m) instance MonadSpinlockLess m => MonadSpinlockLess (StateT s m) -- .... lots of instances
class (Monad m) => MonadSpinlock m instance Monad m => MonadSpinlock (SpinlockT m)
lock :: (MonadSpinlockLess m) => Spinlock -> SpinlockT m a -> m a lock (SL r) h = {- atomicModifyIORef (+1) r (doesn't matter) >> -} unSpinlock h
process :: Spinlock -> IO () process sl = handler_a where
handler_a = do lock sl handler_b
handler_b = do lock sl handler_c {- ^^^^ Second lock, should fail to typecheck -}
handler_c = do {- do something -} return ()
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners