State Transformer

Marcin 'Qrczak' Kowalczyk qrczak@knm.org.pl
Sat, 19 Jan 2002 16:16:34 +0000 (UTC)


11 Jan 2002 17:10:16 -0500, Albert Lai <trebla@vex.net> pisze:

> Now my grief is that I cannot write a subprogram with state
> variables and have it reused in ST and IO.  Fortunately I can write
> a subprogram with mutable arrays and have it reused in ST and IO,
> so I can write "sort a given array"; but I cannot write "increment
> a given integer variable".

You can if you write your own class describing the common interface.

Here is mine. The same code can work with MVars too, as long as the
order of operations is consistent with the empty/full state. The
empty/full state is real for MVars and imagined for IORef/STRef.

module UnifiedRef (Ref(..), STRef, IORef, MVar) where

import ST
import IOExts
import Concurrent

class Monad m => Ref m c | c -> m where
    -- Minimal definition:
    -- 'newRef' or 'newEmptyRef',
    -- 'getRef' or 'cutRef',
    -- 'setRef' or 'insertRef'.
    newRef      :: a -> m (c a)
    newEmptyRef :: m (c a)
    copyRef     :: c a -> m (c a)
    getRef      :: c a -> m a
    setRef      :: c a -> a -> m ()
    cutRef      :: c a -> m a
    insertRef   :: c a -> a -> m ()
    modifyRef   :: c a -> (a -> m a) -> m ()
    withRef     :: c a -> (a -> m b) -> m b
    changeRef   :: c a -> (a -> m (b, a)) -> m b

    newRef      a   = do c <- newEmptyRef; insertRef c a; return c
    newEmptyRef     = newRef (error "Empty reference")
    copyRef     c   = newRef =<< getRef c
    getRef      c   = do a <- cutRef c; insertRef c a; return a
    setRef      c a = do cutRef c; insertRef c a
    cutRef          = getRef
    insertRef       = setRef
    modifyRef   c f = insertRef c =<< f =<< cutRef c
    withRef     c f = do a <- cutRef c; b <- f a; insertRef c a; return b
    changeRef   c f = do a <- cutRef c; (b, a') <- f a; insertRef c a'; return b

instance Ref (ST s) (STRef s) where
    newRef = newSTRef
    getRef = readSTRef
    setRef = writeSTRef

instance Ref IO IORef where
    newRef = newIORef
    getRef = readIORef
    setRef = writeIORef

instance Ref IO MVar where
    newRef        = newMVar
    newEmptyRef   = newEmptyMVar
    getRef        = readMVar
    cutRef        = takeMVar
    insertRef     = putMVar
    modifyRef     = modifyMVar_
    withRef       = withMVar
    changeRef r f = modifyMVar r (\a -> do (b, a') <- f a; return (a', b))

-- 
 __("<  Marcin Kowalczyk * qrczak@knm.org.pl http://qrczak.ids.net.pl/
 \__/
  ^^
QRCZAK