> After a look at Yahu/GIO I decided to use 
set/get/=: in 'HOpenGL: The
 
Good plan. Since wxWindows has an openGL canvas 
widget, we may
want to work more closely on this in the future 
:-)
> My question 
is: The attribute/property/state variable pattern seems to
> be a more 
universal concept than I initially thought, so it might be a
> good idea 
to have support for this in the standard libraries. But
> exactly how is 
not completely clear to me, e.g. GIO uses an additional
> type variable 
(for the kind of widget). Any ideas and/or suggestions?
It certainly seems more generally applicable than 
just gui's. However,
I would suggest a small change to your approach 
where you define a getter
and setter class. Instead, I would focus on 
"attributes".  That is, "get" and
"set" work universally on attributes. Suppose for 
now that we don't use
a write/read only distinction. An attribute has 
both a type "a" and a thing that
it belongs to "w". I wonder why the "thing it 
belongs to" is absent from your
approach as it seems quite fundamental to me. It 
allows you for example to organise
the attributes in type classes and re-use the same 
attribute name for different
kind of things.
data Attr w a   = Attr{ getter :: w -> IO a, setter :: a -> w -> IO () }get :: Attr w a -> w -> IO a
get attr w   = (getter attr) w
For, setting, we use properties -- attributes that 
are already associated with a value. This allows us
to both a bunch of them in lists.
data Prop w  = forall a. Prop (Attr w a) a  -- or even: forall a. (Attr w a) := a
(=:) :: Attr w a -> a -> Prop w
attr =: x   = Prop attr x
Or, if you stick to Haskell98:
data Prop w  = Prop (w -> IO ())
(=:) :: Attr w a -> a -> Prop w
attr =: x   = Prop ((setter attr) x)
And set works like:
set :: [Prop w] -> w -> IO ()
set props w
  = mapM_ (\(Prop setter) -> setter w) props
Now, regarding openGL with state variables, you would make
attributes that work on those, for example:
value :: Attr (IORef a) a
value   = Attr (getIORef)  (setIORef)
So, even openGL will assign attributes to certain kind of things.
Furthermore, you can still make a read/write distinction by putting
"get" and ":=" in classes as you do:
class Readable attr where
  get :: attr w a -> w -> IO a
class Writable attr where
  (=:) :: attr w a -> a -> Prop w
instance Readable Attr where ...
instance Writable Attr where ...
But I am personally a bit hesitant to do this as it 
might give rise
to rather complex error messages -- but only 
experience will show
whether this is actually the case. 
> OK, modules like this look rather 
obvious and small, so why should we
> standardize it at all? Linguistic 
abstraction! Having a set of standard
> functions/operators available for 
a common task is always a good idea,
> it makes other people's programs 
(and old ones written by oneself :-)
 
I totally agree. I hope though that we can find a 
really general abstraction
that will also work for the GUI's or otherwise it 
doesn't make much sense.
Therefore, i am quite curious if the approach that 
is focused on "Attributes"
as sketched in this mail will also work for openGL.
 
All the best,
    Daan.
 
 
 
> much easier to read. Embedding a domain specific language into 
Haskell
> by defining myriads of home-grown operators is often a fine way 
of
> obfuscating a program (Prolog programs are often not much better in 
this
> respect, BTW).
> 
>  > If := is going to be a 
reserved symbol one day, then we should perhaps
>  > not use it. 
[...]
> 
> I wasn't aware of that, but it's just another 
reason...
> 
> Cheers,
>     S.
> 
> _______________________________________________
> GUI mailing 
list
> 
GUI@haskell.org> http://www.haskell.org/mailman/listinfo/gui> 
>