[Haskell-beginners] Immutable refs for the functional code to get emulation of o.o. inner/nested classes
Gabriel Riba
griba2001 at gmail.com
Tue Jan 31 13:56:52 CET 2012
I have worked out a solution with System.IO.Unsafe.unsafePerformIO /
unsafeDupablePerformIO.
I would like any criticism in order to get a good solution.
The idea is to have immutable refs readable safely from the functional code.
Possible use:
--------------------------
import Data.ImmIORef (ImmIORef, newImmIORef, readImmIORef)
data Framework = Framework {prop :: Int}
deriving (Eq, Show)
-- ''Inner'' element with ref. to the framework
data FrameworkElement = FrameworkElement {dta::Int,
frameworkRef :: (ImmIORef Framework)}
deriving (Eq, Show)
getElement'sFramework_Prop :: FrameworkElement -> Int
getElement'sFramework_Prop elem = k
where
k = prop $ readImmIORef $ frameworkRef elem
--------------------------
-- Data.ImmIORef adapted from GHC.IORef
--
module Data.ImmIORef (
ImmIORef,
newImmIORef, readImmIORef
) where
import GHC.Base
import GHC.STRef
import GHC.IO
import Text.Show (Show, show)
import System.IO.Unsafe
-- |An immutable variable in the 'IO' monad
newtype ImmIORef a = ImmIORef (STRef RealWorld a)
-- explicit instance
instance Eq (ImmIORef a) where
ImmIORef x == ImmIORef y = x == y
-- |Build a new 'ImmIORef'
newImmIORef :: a -> IO (ImmIORef a)
newImmIORef v = stToIO (newSTRef v) >>= \ var -> return (ImmIORef var)
-- |Read the value of an 'ImmIORef' via unsafePerformIO
{-# NOINLINE readImmIORef #-} -- recommended in System.IO.Unsafe doc
readImmIORef :: ImmIORef a -> a
#if __GLASGOW_HASKELL__>=721
readImmIORef (ImmIORef var) = unsafeDupablePerformIO $ stToIO (readSTRef var)
#else
readImmIORef (ImmIORef var) = unsafePerformIO $ stToIO (readSTRef var)
#endif
instance (Show a) => Show (ImmIORef a) where
show xRef = "ImmIORef->(" ++ show (readImmIORef xRef) ++ ")"
More information about the Beginners
mailing list