{- * Programmer: Piotr Borek * E-mail: piotrborek@op.pl * Copyright 2017 Piotr Borek * * Distributed under the terms of the GPL (GNU Public License) * * This program is free software; you can redistribute it and/or modify * it under the terms of the GNU General Public License as published by * the Free Software Foundation; either version 2 of the License, or * (at your option) any later version. * * This program is distributed in the hope that it will be useful, * but WITHOUT ANY WARRANTY; without even the implied warranty of * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * GNU General Public License for more details. * * You should have received a copy of the GNU General Public License * along with this program; if not, write to the Free Software * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA -} {-# LANGUAGE BangPatterns #-} module Simple.UI.Core.Attribute ( Attribute, AttributeList, attributeNew, -- attributeNewOverride, get, set, modify, add, add', readAttr, writeAttr, modifyAttr, connectAttrTo ) where import Control.Monad import Control.Monad.IO.Class import Data.IORef newtype Attribute a = Attribute (IORef (a, [Attribute a])) type AttributeList a = Attribute [a] attributeNew :: MonadIO m => a -> m (Attribute a) attributeNew !x = liftIO $ Attribute <$> newIORef (x, []) get :: MonadIO m => s -> (s -> Attribute a) -> m a get obj getAttr = readAttr $ getAttr obj set :: MonadIO m => s -> (s -> Attribute a) -> a -> m () set obj getAttr = writeAttr $ getAttr obj modify :: MonadIO m => s -> (s -> Attribute a) -> (a -> a) -> m () modify obj getAttr = modifyAttr $ getAttr obj add :: MonadIO m => s -> (s -> AttributeList a) -> (b -> a) -> b -> m () add obj getAttr cast !x = modify obj getAttr $ \xs -> xs ++ [cast x] add' :: MonadIO m => s -> (s -> AttributeList a) -> a -> m () add' obj getAttr !x = add obj getAttr id x readAttr :: MonadIO m => Attribute a -> m a readAttr (Attribute attr) = liftIO $ fst <$> readIORef attr writeAttr :: MonadIO m => Attribute a -> a -> m () writeAttr (Attribute attr) !x = liftIO $ do (_ , z1) <- readIORef attr writeIORef attr (x, z1) forM_ z1 $ flip writeAttr x modifyAttr :: MonadIO m => Attribute a -> (a -> a) -> m () modifyAttr attr f = readAttr attr >>= \x -> writeAttr attr (f x) connectAttrTo :: MonadIO m => Attribute a -> Attribute a -> m () connectAttrTo (Attribute from) to = liftIO $ modifyIORef' from $ \(x, z) -> (x, to:z) {- data Attribute a = Attribute { _get :: IO a, _set :: a -> IO () } attributeNew :: MonadIO m => a -> m (Attribute a) attributeNew !x = do ref <- liftIO $ newIORef x return Attribute { _get = liftIO $ readIORef ref, _set = liftIO . writeIORef ref } attributeNewOverride :: IO a -> (a -> IO ()) -> Attribute a attributeNewOverride getter setter = Attribute { _get = getter, _set = setter } get :: MonadIO m => s -> (s -> Attribute a) -> m a get obj getAttr = liftIO $ _get (getAttr obj) set :: MonadIO m => s -> (s -> Attribute a) -> a -> m () set obj getAttr !x = liftIO $ _set (getAttr obj) x modify :: MonadIO m => s -> (s -> Attribute a) -> (a -> a) -> m () modify obj getAttr f = liftIO $ do x <- _get (getAttr obj) _set (getAttr obj) (f x) -}