[GUI] Another RFC on setting and getting.

David Sankel camio@yahoo.com
Tue, 8 Apr 2003 09:01:33 -0700 (PDT)


--- Axel Simon <A.Simon@ukc.ac.uk> wrote:
> > > > - Callbacks get separate functions which
> called
> > > on<WidgetName><ActionName>
> > I agree with this.
> Ok, no problem. 

how About
  doOn<ActionName/>

> > newSomething requiredArgument [attribute := list]
> > 
> > For read-only attributes, you would most always
> want
> > to read the value and nothing else.
> > 
> > h <- getHeight myButton
> I think it would be more systematic (and thus easier
> to
> learn) if we could use "get" here as well.

Seems easy enough, but it isn't.  Lets assume we can
use multiparameter type classes (which is a ghc
extention of haskell).  So we have:

data Attr w a = Attr (w -> IO a) (w -> a -> IO ())  

data AttrRO w a = AttrRO (w -> IO a)

class Attr_Readable s w a where
  getter :: s -> (w -> IO a)

instance Attr_Readable (Attr w a) w a where
  getter (Attr p _) = p

instance Attr_Readable (AttrRO w a) w a where
  getter (AttrRO p) = p

get :: Attr_Readable p w a => w -> p -> IO a 
get w readable = (getter readable) w

now say we have something like:

position :: Attr A_Button (Int,Int)
position = newRWAttr 
  (\w  -> 
    do
      a <- button_memfun_x (b2A w)
      b <- button_memfun_y (b2A w)
      return (a,b) )
  (\w (a,b) -> button_memfun_position (b2A w) a b )


And then in our main do function, we see

p <- get hello size

But it doesn't work!  I got this error:

est_midlevel.hs:20:
    No instance for (Attributes.Attr_Readable
(Attributes.Attr
                                                  
A_Button (Int, Int))
                                              A_Button
                                              a)
    arising from use of `get' at Test_midlevel.hs:20

This is because the return value using those
multiparameter classes is ambigious.  So we are
forcing the users to do something like

get hello size :: IO (Int,Int)

, which sucks.  So I suggest using the getSize type RO
accessors and simply inform the user.

WO variables = constructor/member functions (for
callbacks)
RW variables = attributes
RO variables = member functions

David J. Sankel