{- * 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 -} module Simple.UI.Core.ListenerList ( ListenerID, ListenerList, on, on_, fire, listenerNew, ) where import Control.Monad import Control.Monad.IO.Class import Data.IORef import Simple.UI.Core.Internal.UIApp type ListenerID = Integer type ListenerList a = IORef [(ListenerID, a)] class Fire a b where fire :: w -> (w -> ListenerList a) -> b -> UIApp u () instance Fire (UIApp' ()) () where fire = fire0 instance Fire (a -> UIApp' ()) a where fire = fire1 instance Fire (a -> b -> UIApp' ()) (a, b) where fire = fire2 instance Fire (a -> b -> c -> UIApp' ()) (a, b, c) where fire = fire3 instance Fire (a -> b -> c -> d -> UIApp' ()) (a, b, c, d) where fire = fire4 on :: w -> (w -> ListenerList a) -> a -> UIApp u ListenerID on widget listeners = listenerAdd (listeners widget) on_ :: w -> (w -> ListenerList a) -> a -> UIApp u () on_ widget listeners f = void $ on widget listeners f listenerNew :: MonadIO m => m (ListenerList a) listenerNew = liftIO $ newIORef [] listenerAdd :: ListenerList a -> a -> UIApp u ListenerID listenerAdd listeners f = do listenerID <- uniqueIdNew liftIO $ modifyIORef' listeners $ \xs -> (listenerID, f):xs return listenerID listenerFire0 :: ListenerList (UIApp' ()) -> () -> UIApp u () listenerFire0 listeners _ = do list <- liftIO $ readIORef listeners liftUIApp' $ forM_ list snd fire0 :: w -> (w -> ListenerList (UIApp' ())) -> () -> UIApp u () fire0 widget listeners = listenerFire0 (listeners widget) listenerFire1 :: ListenerList (a -> UIApp' ()) -> a -> UIApp u () listenerFire1 listeners a0 = do list <- liftIO $ readIORef listeners liftUIApp' $ forM_ list $ \(_, f) -> f a0 fire1 :: w -> (w -> ListenerList (a -> UIApp' ())) -> a -> UIApp u () fire1 widget listeners = listenerFire1 (listeners widget) listenerFire2 :: ListenerList (a -> b -> UIApp' ()) -> (a, b) -> UIApp u () listenerFire2 listeners (a0, a1) = do list <- liftIO $ readIORef listeners liftUIApp' $ forM_ list $ \(_, f) -> f a0 a1 fire2 :: w -> (w -> ListenerList (a -> b -> UIApp' ())) -> (a, b) -> UIApp u () fire2 widget listeners = listenerFire2 (listeners widget) listenerFire3 :: ListenerList (a -> b -> c -> UIApp' ()) -> (a, b, c) -> UIApp u () listenerFire3 listeners (a0, a1, a2) = do list <- liftIO $ readIORef listeners liftUIApp' $ forM_ list $ \(_, f) -> f a0 a1 a2 fire3 :: w -> (w -> ListenerList (a -> b -> c -> UIApp' ())) -> (a, b, c) -> UIApp u () fire3 widget listeners = listenerFire3 (listeners widget) listenerFire4 :: ListenerList (a -> b -> c -> d -> UIApp' ()) -> (a, b, c, d) -> UIApp u () listenerFire4 listeners (a0, a1, a2, a3) = do list <- liftIO $ readIORef listeners liftUIApp' $ forM_ list $ \(_, f) -> f a0 a1 a2 a3 fire4 :: w -> (w -> ListenerList (a -> b -> c -> d -> UIApp' ())) -> (a, b, c, d) -> UIApp u () fire4 widget listeners = listenerFire4 (listeners widget)