{-# LANGUAGE Trustworthy #-} ----------------------------------------------------------------------------- -- | -- Module : Data.STRef -- Copyright : (c) The University of Glasgow 2001 -- License : BSD-style (see the file libraries/base/LICENSE) -- -- Maintainer : libraries@haskell.org -- Stability : experimental -- Portability : non-portable (uses Control.Monad.ST) -- -- Mutable references in the (strict) ST monad. -- ----------------------------------------------------------------------------- module Data.STRef ( -- * STRefs STRef, -- abstract newSTRef, readSTRef, writeSTRef, modifySTRef, modifySTRef' ) where import GHC.ST import GHC.STRef -- | Mutate the contents of an 'STRef'. -- -- >>> :{ -- runST (do -- ref <- newSTRef "" -- modifySTRef ref (const "world") -- modifySTRef ref (++ "!") -- modifySTRef ref ("Hello, " ++) -- readSTRef ref ) -- :} -- "Hello, world!" -- -- Be warned that 'modifySTRef' does not apply the function strictly. This -- means if the program calls 'modifySTRef' many times, but seldom uses the -- value, thunks will pile up in memory resulting in a space leak. This is a -- common mistake made when using an 'STRef' as a counter. For example, the -- following will leak memory and may produce a stack overflow: -- -- >>> import Control.Monad (replicateM_) -- >>> :{ -- print (runST (do -- ref <- newSTRef 0 -- replicateM_ 1000 $ modifySTRef ref (+1) -- readSTRef ref )) -- :} -- 1000 -- -- To avoid this problem, use 'modifySTRef'' instead. modifySTRef :: STRef s a -> (a -> a) -> ST s () modifySTRef :: forall s a. STRef s a -> (a -> a) -> ST s () modifySTRef STRef s a ref a -> a f = STRef s a -> a -> ST s () forall s a. STRef s a -> a -> ST s () writeSTRef STRef s a ref (a -> ST s ()) -> (a -> a) -> a -> ST s () forall b c a. (b -> c) -> (a -> b) -> a -> c . a -> a f (a -> ST s ()) -> ST s a -> ST s () forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b =<< STRef s a -> ST s a forall s a. STRef s a -> ST s a readSTRef STRef s a ref -- | Strict version of 'modifySTRef' -- -- @since 4.6.0.0 modifySTRef' :: STRef s a -> (a -> a) -> ST s () modifySTRef' :: forall s a. STRef s a -> (a -> a) -> ST s () modifySTRef' STRef s a ref a -> a f = do a x <- STRef s a -> ST s a forall s a. STRef s a -> ST s a readSTRef STRef s a ref let x' :: a x' = a -> a f a x a x' a -> ST s () -> ST s () `seq` STRef s a -> a -> ST s () forall s a. STRef s a -> a -> ST s () writeSTRef STRef s a ref a x'