Tying a simple circularly STM linked list

Hi, I've written a circularly linked list, but there is some code in it I feel is redundant, but don't know how to get rid of: -- Transactional loop. A loop is a circular link list. data Loop a = ItemLink { item :: a , prev :: TVar (Loop a) , next :: TVar (Loop a) } | InitLink -- Create a new empty transactional loop. newLoop :: a -> STM (TVar (Loop a)) newLoop item = do tLoop <- newTVar InitLink writeTVar tLoop (ItemLink item tLoop tLoop) return tLoop In the above, the InitLink value is only ever used in the newLoop function to create a single one element circular linked list. Is there a way to write newLoop to avoid using this value? Thanks -John

You can use "undefined" or "error ..." :
{-# LANGUAGE RecursiveDo #-} import Control.Concurrent.STM import Control.Monad.Fix
-- Transactional loop. A loop is a circular link list. data Loop a = ItemLink { item :: a , prev :: TVar (Loop a) , next :: TVar (Loop a) }
-- Create a new empty transactional loop. newLoop :: a -> STM (TVar (Loop a)) newLoop item = do tLoop <- newTVar undefined writeTVar tLoop (ItemLink item tLoop tLoop) return tLoop
Hmmm.. STM does not have a MonadFix instance. But IO does:
-- Use MonadFix instance of newLoopIO newLoopIO :: a -> IO (TVar (Loop a)) newLoopIO item = mfix (\ tLoop -> newTVarIO (ItemLink item tLoop tLoop))
But mfix (like fix) is difficult to read in large amounts, so there is "mdo":
-- Use RecursiveDo notation newLoopMDO :: a -> IO (TVar (Loop a)) newLoopMDO item = mdo tLoop <- newTVarIO (ItemLink item tLoop tLoop) return tLoop
Cheers, Chris

Thanks Chris,
The undefined works for me.
-John
On Wed, Jan 7, 2009 at 11:11 AM, ChrisK
You can use "undefined" or "error ..." :
{-# LANGUAGE RecursiveDo #-}
import Control.Concurrent.STM import Control.Monad.Fix
-- Transactional loop. A loop is a circular link list. data Loop a = ItemLink { item :: a , prev :: TVar (Loop a) , next :: TVar (Loop a) }
-- Create a new empty transactional loop. newLoop :: a -> STM (TVar (Loop a)) newLoop item = do tLoop <- newTVar undefined writeTVar tLoop (ItemLink item tLoop tLoop) return tLoop
Hmmm.. STM does not have a MonadFix instance. But IO does:
-- Use MonadFix instance of newLoopIO newLoopIO :: a -> IO (TVar (Loop a)) newLoopIO item = mfix (\ tLoop -> newTVarIO (ItemLink item tLoop tLoop))
But mfix (like fix) is difficult to read in large amounts, so there is "mdo":
-- Use RecursiveDo notation
newLoopMDO :: a -> IO (TVar (Loop a)) newLoopMDO item = mdo tLoop <- newTVarIO (ItemLink item tLoop tLoop) return tLoop
Cheers, Chris
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (2)
-
ChrisK
-
John Ky