module Component where import Data.IORef import Control.Applicative -- reference management: newtype Ref a = Ref (IORef a) infixr 0 .<, .<<, .>, .>> (.>>) :: Ref (state) -> (state -> IO a) -> IO a (.>>) (Ref c) a = readIORef c >>= a (.<<) :: Ref (state) -> (state -> IO state) -> IO () (.<<) (Ref c) a = readIORef c >>= a >>= writeIORef c (.<) :: Ref (state) -> (state -> state) -> IO () (.<) (Ref c) a = readIORef c >>= writeIORef c . a (.>) :: Ref (state) -> (state -> a) -> IO a (.>) c getter = c .>> return . getter newRef :: state -> IO (Ref (state)) newRef c = Ref <$> newIORef c unRef :: Ref (state) -> IO (state) unRef (Ref c) = readIORef c