Difference between revisions of "Mutable variable"

From HaskellWiki
Jump to navigation Jump to search
(Haskell 98 solution)
(data-ref)
Line 6: Line 6:
 
* {{HackagePackage|id=ArrayRef}}, module <hask>Data.Ref.Universal</hask>
 
* {{HackagePackage|id=ArrayRef}}, module <hask>Data.Ref.Universal</hask>
 
* {{HackagePackage|id=binding-core}}, module <hask>Data.Variable</hask>
 
* {{HackagePackage|id=binding-core}}, module <hask>Data.Variable</hask>
  +
* {{HackagePackage|id=data-ref}}
 
* {{HackagePackage|id=monad-statevar}}
 
* {{HackagePackage|id=monad-statevar}}
 
* {{HackagePackage|id=ref-fd}}
 
* {{HackagePackage|id=ref-fd}}
Line 16: Line 17:
 
== Haskell 98 solution ==
 
== Haskell 98 solution ==
   
If the type of the reference depends only on the monad then there is an elegant Haskell 98 solution:
+
If the type of the reference depends only on the monad then there is an elegant Haskell 98 solution,
  +
as implemented in the {{HackagePackage|id=data-ref}} package:
   
 
<haskell>
 
<haskell>

Revision as of 16:48, 15 July 2013

Although the functional programming paradigm emphasises the virtues of immutable variables, sometimes you need mutable variables nonetheless. You can either simulate mutable variables using the state monad provided for instance by Control.Monad.Trans.State in the transformers package or you can use really mutable variables as provided by Data.IORef or Data.STRef or Control.Concurrent.STM.TVar from the stm package. In either case you need a monad in order to cope with mutability, while staying purely functional.

There are several packages that provide a single interface to these different implementations of mutable variables (in alphabetical order):

Haskell 98 solution

If the type of the reference depends only on the monad then there is an elegant Haskell 98 solution, as implemented in the data-ref package:

module Data.Ref where

import Data.IORef (newIORef, readIORef, writeIORef, )
import Data.STRef (newSTRef, readSTRef, writeSTRef, )
import Control.Concurrent.STM.TVar (newTVar, readTVar, writeTVar, )
import Control.Concurrent.STM (STM, )
import Control.Monad.ST (ST)
import Prelude hiding (read)


data T m a = Cons { write :: a -> m (), read :: m a }

modify :: Monad m => T m a -> (a -> a) -> m ()
modify ref f = write ref . f =<< read ref


class C m where
   new :: a -> m (T m a)

instance C IO where
   new = fmap (\r -> Cons (writeIORef r) (readIORef r)) . newIORef

instance C (ST s) where
   new = fmap (\r -> Cons (writeSTRef r) (readSTRef r)) . newSTRef

instance C STM where
   new = fmap (\r -> Cons (writeTVar r) (readTVar r)) . newTVar


See also