[Haskell-cafe] Re: Tying a simple circularly STM linked list
John Ky
newhoggy at gmail.com
Wed Jan 7 21:54:23 EST 2009
Thanks Chris,
The undefined works for me.
-John
On Wed, Jan 7, 2009 at 11:11 AM, ChrisK <haskell at list.mightyreason.com>wrote:
> 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 at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20090108/b2418aca/attachment.htm
More information about the Haskell-Cafe
mailing list