Mutable variable
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):
- binding-core, module
Data.Variable
- data-ref
- ref-fd
- ref-tf
- StateVar
Haskell 98 solution[edit]
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[edit]
- Haskell Libraries mailing list on "suggestion: A common type class for mutable variables" in May and June, 2013
- Library/ArrayRef
- A unified interface to mutable variables as an example for Multi-parameter type classes