Difference between revisions of "PropLang"

From HaskellWiki
Jump to navigation Jump to search
Line 12: Line 12:
   
 
data Var a = ...
 
data Var a = ...
data Notify
+
data Notify = ...
   
 
get :: Var a -> IO a
 
get :: Var a -> IO a
Line 20: Line 20:
   
 
newVar :: a -> IO (Var a)
 
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 (Action a))}
  +
  +
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 ==
 
== Object layering ==

Revision as of 14:34, 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 (Action a))}
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 -> IO ()
with :: Var a -> (a -> b) -> Action b