PropLang: Difference between revisions
NeilMitchell (talk | contribs) No edit summary |
NeilMitchell (talk | contribs) No edit summary |
||
Line 28: | Line 28: | ||
notifyId :: IORef Integer, | notifyId :: IORef Integer, | ||
notifys :: IORef [(Integer, a -> IO ())], | notifys :: IORef [(Integer, a -> IO ())], | ||
source :: IORef (Maybe | source :: IORef (Maybe Notify)} | ||
data Notify = Notify {notifyId :: Integer, notifys :: IORef [(Integer, a -> IO ())]} | data Notify = Notify {notifyId :: Integer, notifys :: IORef [(Integer, a -> IO ())]} | ||
Line 60: | Line 60: | ||
== Object layering == | == Object layering == | ||
textBox | textBox~text -< "test" | ||
filename <- newVar Nothing | filename <- newVar Nothing | ||
addNotify filename hatCover | addNotify filename hatCover | ||
lbl | lbl~text =< with filename $ \x -> | ||
case x of | case x of | ||
Nothing -> "Select a file" | Nothing -> "Select a file" | ||
Line 71: | Line 71: | ||
where | where | ||
( | (~) :: GtkObject -> GtkProp -> Var a -- ignoring lots of details here | ||
(-<) :: Var a -> a -> IO () | (-<) :: Var a -> a -> IO () | ||
(=<) :: Var a -> Action a b -> IO () | |||
with :: Var a -> (a -> b) -> Action a b | |||
== Implementation of Object Layering == | |||
data Action a b = Action (Var a) (a -> b) | |||
with :: Var a -> (a -> b) -> Action a b | |||
with var f = Action var f | |||
(-<) :: Var a -> a -> IO () | |||
(-<) var val = set var val | |||
(=<) :: Var a -> Action a -> IO () | (=<) :: Var a -> Action a -> IO () | ||
(=<) dest (Act src f) = do srcOld <- readIORef (source dest) | |||
when (isJust srcOld) $ remNotify (fromJust srcOld) | |||
note <- addNotify src (\x -> set dest (f x)) | |||
writeIORef (source dest) (Just note) |
Revision as of 14:41, 18 July 2006
A design for a GUI library which is more like Haskell and less like C. To be written over Gtk2Hs.
Link: http://www.cse.unsw.edu.au/~chak/haskell/ports/
Thoughts by
Neil Mitchell, Duncan Coutts
The Var concept
This is the low level stuff, on which the library will be built
data Var a = ... data Notify = ...
get :: Var a -> IO a set :: Var a -> a -> IO () addNotify :: Var a -> (a -> IO ()) -> IO Notify remNotify :: Notify -> IO ()
newVar :: a -> IO (Var a)
A concrete implementation of Var
One thing to avoid, global state that needs a specific init function
data Var a = Var {value :: IORef a, notifyId :: IORef Integer, notifys :: IORef [(Integer, a -> IO ())], source :: IORef (Maybe Notify)}
data Notify = Notify {notifyId :: Integer, notifys :: IORef [(Integer, a -> IO ())]}
newVar :: a -> IO (Var a) newVar x = do v <- newIORef x n <- newIORef [] c <- newIORef 0 a <- newIORef Nothing return $ Var v c n a
get :: Var a -> IO a get var = readIORef (value var)
set :: Var a -> a -> IO () set var x = do n <- readIORef (notifys var) writeIORef (value var) x mapM_ (\(a,b) -> b x) n
addNotify :: Var a -> (a -> IO ()) -> IO Notify addNotify var f = do n <- readIORef (notifys var) c <- readIORef (notifyId var) writeIORef (notifyId var) (c+1) writeIORef (notifys var) ((c, f) : n) return $ Notify c (notifys var)
remNotify :: Notify -> IO () remNotify notify = do n <- readIORef (notifys notify) writeIORef (notifys notify) (filter (\x -> fst x /= notifyId notify) n)
Object layering
textBox~text -< "test" filename <- newVar Nothing addNotify filename hatCover lbl~text =< with filename $ \x -> case x of Nothing -> "Select a file" Just x -> "Loaded: " ++ x
where
(~) :: GtkObject -> GtkProp -> Var a -- ignoring lots of details here (-<) :: Var a -> a -> IO () (=<) :: Var a -> Action a b -> IO ()
with :: Var a -> (a -> b) -> Action a b
Implementation of Object Layering
data Action a b = Action (Var a) (a -> b)
with :: Var a -> (a -> b) -> Action a b with var f = Action var f
(-<) :: Var a -> a -> IO () (-<) var val = set var val
(=<) :: Var a -> Action a -> IO () (=<) dest (Act src f) = do srcOld <- readIORef (source dest) when (isJust srcOld) $ remNotify (fromJust srcOld) note <- addNotify src (\x -> set dest (f x)) writeIORef (source dest) (Just note)