RE: Xlib IDL for H/Direct?

1999-03-25 Thread Sigbjorn Finne (Intl Vendor)


Frank A. Christoph <[EMAIL PROTECTED]> writes: 
> 
> Has anyone created an IDL file for Xlib? Alternatively, has 
> anyone created one for H/Direct?
> 
> I know that someone is working on GTK, but I'm interested in 
> Xlib specifically. Also, I'm aware of Sigbjorn's Xlib 
> interface in Haggis, but that one's reportedly still for GHC 0.29. :(
> 

You could write a Haskell to IDL tysig translator, I suppose ;-)
I've got a ghc-3.xx translation of these Xlib stubs, which I 
no doubt could dig up and distribute to interested parties.

> BTW, it's not urgent---I don't have any experience with 
> either Xlib or H/Direct yet; I just want to play around with 
> them. Having unsuccessfully checked the net for a suitable 
> IDL description, I'm taking a shot at writing one myself, and 
> I have a couple questions. (If I ever get this into a usable 
> form, I'll notify you all.)
> 

I like this - such an IDL spec would have the potential of
being compilable with CamlIDL as well, which is Really Great
(and the very reason why IDL was introduced in the first place).

> First, judging from the DCE grammar it looks like you can't 
> specify attributes for constants. In a constant definition like
> 
>   const char *XNCursor = "cursor";
> 
> will H/Direct figure out the right interpretation for char *?
> 

Yes.

> Do I need to specify an attribute (ref, ptr, unique, ..) for 
> every occurrence of a * type in a struct field, or is there a 
> default? The user manual seems to imply that translation of 
> char * types default to [string], but I didn't see any 
> mention of this in my perusal of the DCE spec. The technical 
> report on H/Direct mentions a "pointer default" in connection 
> with the internal translation into core IDL; the DCE spec 
> mentions that you can set a pointer default by setting it on 
> an interface. What about at top level? Is the default just 
> [ptr] for non-char * cases?
> 

As far as I know, there's no mechanism for giving global pointer
defaults. However, if you embed the 'const' inside a module {}
declaration, you can give it a pointer default.

The default-default annotation is [unique] for struct ptrs. However,
HDirect honours [pointer_default()] on structs, 

  struct tagList;
  typedef [pointer_default(ref)]struct tagList {
 valUnion* val;
 [unique]struct tagList* next;
  } LList;


> There is a function which takes an argument that is a pointer 
> to an allocated struct, and deallocates it. What is the 
> correct annotation for this behavior?
> 

If I understand correctly,

  void freeStruct([in,ptr]Struct* p);


> xlib.h has a macro:
> 
>   #define Bool int
> 
> Is it safe to translate this as
> 
>   typedef boolean Bool;
> 
> ? Apparently the "recommended" C-translation for boolean is char...
> 

Yes, I'd suggest just doing a literal translation of the #define,

  typedef int Bool;

and avoid the booleans-in-C debacle.

> Finally, any ideas on how to handle callbacks...? Any other 
> special provisos or advice on dealing with Xlib?
> 

A couple of things:

- parked on my HDD is a version of HDirect that handles IDL function
  types correctly and automatically; to be released shortly.

- The Concurrent Haskell implementation in ghc-4.xx doesn't currently
  have support for doing non-blocking waits on I/O from file descriptors,
  which means that you may have to busy wait on incoming events from
  the X server.

- support Manuel's GTK+ efforts, if possible; Xlib is low-level, and GTK+
  (and its Glib) does hold out the promise of being cross-platform one
  day soon.

- I've been meaning to write a cheap&cheerful header file to IDL
  pre-processor, but have never gotten around to actually doing it. This
  would be of some help to you here, I suppose.

hth,
--sigbjorn



RE: Xlib IDL for H/Direct?

1999-03-26 Thread Manuel M. T. Chakravarty

"Sigbjorn Finne (Intl Vendor)" <[EMAIL PROTECTED]> wrote,

[...lots of stuff deleted...]
>
> A couple of things:
> 
[...]
> - support Manuel's GTK+ efforts, if possible; Xlib is low-level, and GTK+
>   (and its Glib) does hold out the promise of being cross-platform one
>   day soon.

I will provide explicit support for Glib and GDK also.
Actually, I am currently restructuring the code to directly
reflect the Glib/GDK/GTK+ trinity on the Haskell side.  That
is quite important as GTK+ requires the programmer to
directly access GDK for things like using alternative input
devices (eg, graphic tablets) and using rendering libraries
like Sven's OpenGL binding.
 
> - I've been meaning to write a cheap&cheerful header file to IDL
>   pre-processor, but have never gotten around to actually doing it. This
>   would be of some help to you here, I suppose.

At the moment, I am implementing a C header file parser to
automatically ensure consistency of enumeration types etc
between the original GTK+ headers and the Haskell binding.
I'll put the stuff on the net when it works.

Cheers,

Manuel



Re: Xlib IDL for H/Direct?

1999-03-26 Thread Sven Panne

"Manuel M. T. Chakravarty" wrote:
> [...] That is quite important as GTK+ requires the programmer to
> directly access GDK for things like using alternative input
> devices (eg, graphic tablets) and using rendering libraries
> like Sven's OpenGL binding.

OK, OK, the discreet hint has been understood... :-)  If the weather
allows it, I'll try to assemble a pre-release HOpenGL this weekend.
It's not complete, but I'd like to get some feedback. Another downside
is that relatively new versions of GHC and Green Card will be needed
to compile it.

Regarding the GTK+/OpenGL-glue: It seems that GtkGLArea is still
actively maintained and more powerful than gtkGL, but I don't have
much experience with either of them. Comments or suggestions are
highly welcome.

> At the moment, I am implementing a C header file parser to
> automatically ensure consistency of enumeration types etc
> between the original GTK+ headers and the Haskell binding. [...]

What's wrong with using Green Card? Its %enum generates the desired
mappings automatically and consistently. AFAIK, this type safety is
something even IDL compilers don't do for you. E.g. I have an OpenGL IDL
lying around here with which it's no problem passing a matrix mode as a
texture name because almost everything is mapped to Int.  :-P
But I'd like to be proved wrong...

Cheers,
   Sven
-- 
Sven PanneTel.: +49/89/2178-2235
LMU, Institut fuer Informatik FAX : +49/89/2178-2211
LFE Programmier- und Modellierungssprachen  Oettingenstr. 67
mailto:[EMAIL PROTECTED]D-80538 Muenchen
http://www.pms.informatik.uni-muenchen.de/mitarbeiter/panne



Re: Xlib IDL for H/Direct?

1999-03-29 Thread Manuel M. T. Chakravarty

Sven Panne <[EMAIL PROTECTED]> wrote,

> "Manuel M. T. Chakravarty" wrote:
> > [...] That is quite important as GTK+ requires the programmer to
> > directly access GDK for things like using alternative input
> > devices (eg, graphic tablets) and using rendering libraries
> > like Sven's OpenGL binding.
> 
> OK, OK, the discreet hint has been understood... :-)  If the weather
> allows it, I'll try to assemble a pre-release HOpenGL this weekend.
> It's not complete, but I'd like to get some feedback. 

Great :-)

In exchange, I promise that I make the GTK+ functionality
needed for HOpenGL a high priority.

> Another downside
> is that relatively new versions of GHC and Green Card will be needed
> to compile it.

Living on the edge can be fun and it is always nice to have
a good excuse for updating ones software installation ;-)

> Regarding the GTK+/OpenGL-glue: It seems that GtkGLArea is still
> actively maintained and more powerful than gtkGL, but I don't have
> much experience with either of them. Comments or suggestions are
> highly welcome.

Judging from the GTK+ mailing list, GtkGLArea definitely
seems to be the more active one - a good reason to use it if 
there are not any strong technical reasons against it.

> > At the moment, I am implementing a C header file parser to
> > automatically ensure consistency of enumeration types etc
> > between the original GTK+ headers and the Haskell binding. [...]
> 
> What's wrong with using Green Card? Its %enum generates the desired
> mappings automatically and consistently. AFAIK, this type safety is
> something even IDL compilers don't do for you. E.g. I have an OpenGL IDL
> lying around here with which it's no problem passing a matrix mode as a
> texture name because almost everything is mapped to Int.  :-P
> But I'd like to be proved wrong...

When I started, I of course thought about using Green Card
or HDirect.  I didn't use Green Card, because HDirect seems
to be positioned as its successor (and I don't know if in
the long run, both will be supported).  I didn't use HDirect
because (a) it is still quite "beta" and (b) I think it would
be an overkill.

Re (b): Most of the time that I put into the binding so far
was spent on design of the Haskell API and its mapping to
the C API.  Writing the marshaling code etc was quite
painless and that's the only place where HDirect would have
helped.  (The situation may be different for other
libraries, though.)  What I really like is the new FFI!  I
definitely think, it should be considered for inclusion in
the Haskell standard.  (How about, Haskell 2k = Haskell 98 + 
FFI? ;-)

However, I found that there is a certain type of material in
the binding code that, I think, I can generate from the C
header file.  Therefore, I am currently implementing a C
header file parser.  BTW a nice experience in itself...do
you know what

  const struct bla {int y;} typedef foo (int x),
  bar (char z);

declares?

Regarding HDirect, I think, its time comes when we want to
have CORBA support for using Gnome from Haskell.

Cheers,

Manuel



Re: Xlib IDL for H/Direct?

1999-03-29 Thread Sven Panne

"Sigbjorn Finne (Intl Vendor)" wrote:
> Sven Panne wrote:
> > What's wrong with using Green Card? Its %enum generates the desired
> > mappings automatically and consistently. AFAIK, this type safety is
> > something even IDL compilers don't do for you.
> 
> Use whatever works best for you, but I'm not sure I agree with this
> statement re: enums. Care to expand? :)

OK, my mail was a little bit terse, so I'll try again with a hopefully
self-explaining example. First in IDL:

-- Foo.idl --
module Foo {

const int EXIT_FAILURE = 1;
const int EXIT_SUCCESS = 0;
typedef int status_t;
void exit ([in]status_t status);

const int SEEK_SET = 0;
const int SEEK_CUR = 1;
const int SEEK_END = 2;
typedef int whence_t;

typedef unsigned long off_t;
typedef int fd_t;
off_t lseek([in]fd_t fd, [in]off_t offset, [in]whence_t whence);
}
-

And here in Green Card:

-- Bar.gc ---
module Bar where

import StdDIS
import Word

%enum Status Int [ EXIT_FAILURE, EXIT_SUCCESS ]
%fun exit :: Status -> IO ()

%enum Whence Int [ SEEK_SET, SEEK_CUR, SEEK_END ]

newtype Offset = Offset Word32;
%dis offset x = Offset (word32 x)

newtype Fd = Fd Int;
%dis fd x = Fd (int x)

%fun lseek :: Fd -> Offset -> Whence -> IO Offset
-

With Foo, the following silly things are possible (i.e. pass the
compiler silently):

   import Foo
   main = do print (eXIT_SUCCESS ^ sEEK_END + 42)
 lseek sEEK_CUR 99 eXIT_FAILURE
 exit sEEK_SET

Some of the errors in this code snippet seem artificial, but to be
honest, who knows the exact arguments of lseek without peeking into
the man pages (or /usr/include/unistd.h :-)  ?

With the Green Card version of the interface these kind of mistakes
are impossible because they lead to compile time errors. An additional
bonus: If e.g. some day, in a sudden fit of craziness, the POSIX people
decide to change the value of SEEK_END to 0xAFFE, you have to change
Foo.idl, but not Bar.gc.

I'm not an IDL grand master, so my question to the H/Direct wizards:
Is there a *simple* way to get a similar thing using IDL without
writing the marshalling/unmarshalling stuff by hand?

Cheers,
   Sven

P.S.: The DIS's (or DISes? Hmm...) for the newtypes in Bar.gc could
easily generated by Green Card, giving even less chance to get things
wrong. But I think this is already on the ToDo list.
-- 
Sven PanneTel.: +49/89/2178-2235
LMU, Institut fuer Informatik FAX : +49/89/2178-2211
LFE Programmier- und Modellierungssprachen  Oettingenstr. 67
mailto:[EMAIL PROTECTED]D-80538 Muenchen
http://www.pms.informatik.uni-muenchen.de/mitarbeiter/panne



RE: Xlib IDL for H/Direct?

1999-03-29 Thread Sigbjorn Finne (Intl Vendor)



> Sven Panne [mailto:[EMAIL PROTECTED]] writes: 
> 
> "Sigbjorn Finne (Intl Vendor)" wrote:
> > Sven Panne wrote:
> > > What's wrong with using Green Card? Its %enum generates 
> > > the desired mappings automatically and consistently. AFAIK,
> > > this type safety is something even IDL compilers don't do
> > > for you.
> > 
> > Use whatever works best for you, but I'm not sure I agree with this
> > statement re: enums. Care to expand? :)
> 
> OK, my mail was a little bit terse, so I'll try again with a hopefully
> self-explaining example. First in IDL:
> 
> -- Foo.idl --
> module Foo {
> 
> const int EXIT_FAILURE = 1;
> const int EXIT_SUCCESS = 0;
> typedef int status_t;
> void exit ([in]status_t status);
> 
> const int SEEK_SET = 0;
> const int SEEK_CUR = 1;
> const int SEEK_END = 2;
> typedef int whence_t;
> 
> typedef unsigned long off_t;
> typedef int fd_t;
> off_t lseek([in]fd_t fd, [in]off_t offset, [in]whence_t whence);
> }
> -
> 
> And here in Green Card:
> 
> -- Bar.gc ---
> module Bar where
> 
> import StdDIS
> import Word
> 
> %enum Status Int [ EXIT_FAILURE, EXIT_SUCCESS ]
> %fun exit :: Status -> IO ()
> 
> %enum Whence Int [ SEEK_SET, SEEK_CUR, SEEK_END ]
> 
> newtype Offset = Offset Word32;
> %dis offset x = Offset (word32 x)
> 
> newtype Fd = Fd Int;
> %dis fd x = Fd (int x)
> 
> %fun lseek :: Fd -> Offset -> Whence -> IO Offset
> -
> 

You could use 'const's for this, but I'd suggest using an
'enum' decl in IDL instead. IDL 'enum' declarations are just
like in C, but HDirect extends 'em a little by supporting
the custom 'deriving()' attribute. For example,

 typedef [deriving("Eq")]
   enum { EXIT_FAILURE = 0, EXIT_SUCCESS } Status;

gives

 data Status = EXIT_FAILURE | EXIT_SUCCESS

 instance Eq   Status where {...}
 instance Enum Status where {...}

which should be equal in power to %enum. (HDirect doesn't
currently allow you to map enums to newtypes of Int (say),
but it could. No big deal).

--sigbjorn



Re: Xlib IDL for H/Direct?

1999-03-29 Thread Sven Panne

"Sigbjorn Finne (Intl Vendor)" wrote:
> You could use 'const's for this, but I'd suggest using an
> 'enum' decl in IDL instead.

Uhmmm, I should have read the docs more closely... :-]   But there's
a little bug when using -fenum-instances (missing returns):

   ...
   marshallStatus :: Status -> Prelude.IO Int.Int32
   marshallStatus v =
 case v of
EXIT_FAILURE -> 0
EXIT_SUCCESS -> 1
   ...

> IDL 'enum' declarations are just like in C, but HDirect extends 'em
> a little by supporting the custom 'deriving()' attribute. For example,
> 
>  typedef [deriving("Eq")]
>enum { EXIT_FAILURE = 0, EXIT_SUCCESS } Status;
> 
> gives
> 
>  data Status = EXIT_FAILURE | EXIT_SUCCESS
> 
>  instance Eq   Status where {...}
>  instance Enum Status where {...}
> 
> which should be equal in power to %enum.

I don't get the Eq instance with my local hdirect-0.14. Are there any
special flags I forgot this time?

> (HDirect doesn't currently allow you to map enums to newtypes of Int
> (say), but it could. No big deal).

Hmm, IMHO it's not enum that should be mapped to newtype but a simple
typedef: Enums have a certain bounded set of possible values while
something like 'typedef unsigned long off_t' has not (at least
conceptually). I consider the automatic wrapping/unwrapping into
newtypes as a crucial feature of any kind of type-safe IDL, so it
should definitely included into H/Direct.

Cheers,
   Sven
-- 
Sven PanneTel.: +49/89/2178-2235
LMU, Institut fuer Informatik FAX : +49/89/2178-2211
LFE Programmier- und Modellierungssprachen  Oettingenstr. 67
mailto:[EMAIL PROTECTED]D-80538 Muenchen
http://www.pms.informatik.uni-muenchen.de/mitarbeiter/panne



RE: Xlib IDL for H/Direct?

1999-03-29 Thread Sigbjorn Finne (Intl Vendor)


Sven Panne <[EMAIL PROTECTED]> writes: 
> 
...
> 
> > (HDirect doesn't currently allow you to map enums to newtypes of Int
> > (say), but it could. No big deal).
> 
> Hmm, IMHO it's not enum that should be mapped to newtype but a simple
> typedef: Enums have a certain bounded set of possible values while
> something like 'typedef unsigned long off_t' has not (at least
> conceptually). I consider the automatic wrapping/unwrapping into
> newtypes as a crucial feature of any kind of type-safe IDL, so it
> should definitely included into H/Direct.
> 

That's a different issue; you can use 'interface {}' decls to achieve
this kind of type safety.

--sigbjorn



RE: Xlib IDL for H/Direct?

1999-03-30 Thread Manuel M. T. Chakravarty

"Sigbjorn Finne (Intl Vendor)" <[EMAIL PROTECTED]> wrote,

> > Sven Panne [mailto:[EMAIL PROTECTED]] writes: 
> > 
> > "Sigbjorn Finne (Intl Vendor)" wrote:
> > > Sven Panne wrote:
> > > > What's wrong with using Green Card? Its %enum generates 
> > > > the desired mappings automatically and consistently. AFAIK,
> > > > this type safety is something even IDL compilers don't do
> > > > for you.
> > > 
> > > Use whatever works best for you, but I'm not sure I agree with this
> > > statement re: enums. Care to expand? :)
> > 
[...]
> > 
> > And here in Green Card:
> > 
> > -- Bar.gc ---
> > module Bar where
> > 
> > import StdDIS
> > import Word
> > 
> > %enum Status Int [ EXIT_FAILURE, EXIT_SUCCESS ]
> > %fun exit :: Status -> IO ()
> > 
> > %enum Whence Int [ SEEK_SET, SEEK_CUR, SEEK_END ]
> > 
> > newtype Offset = Offset Word32;
> > %dis offset x = Offset (word32 x)
> > 
> > newtype Fd = Fd Int;
> > %dis fd x = Fd (int x)
> > 
> > %fun lseek :: Fd -> Offset -> Whence -> IO Offset
> > -
> > 
> 
> You could use 'const's for this, but I'd suggest using an
> 'enum' decl in IDL instead. IDL 'enum' declarations are just
> like in C, but HDirect extends 'em a little by supporting
> the custom 'deriving()' attribute. For example,
> 
>  typedef [deriving("Eq")]
>enum { EXIT_FAILURE = 0, EXIT_SUCCESS } Status;
> 
> gives
> 
>  data Status = EXIT_FAILURE | EXIT_SUCCESS
> 
>  instance Eq   Status where {...}
>  instance Enum Status where {...}
> 
> which should be equal in power to %enum.

Isn't there still a difference?  When the C-library changes
(ie, you get a new version) and the definition of `Status'
changes to

  enum Status {
EXIT_FAILURE = -1;
EXIT_SUCCESS = 0;
  }

The IDL binding would produce wrong code, but the Green Card
binding would still be correct.  Right?  Or do I miss
something?

Manuel



Re: Xlib IDL for H/Direct?

1999-03-30 Thread Sven Panne

"Manuel M. T. Chakravarty" wrote:
> Isn't there still a difference?  When the C-library changes
> (ie, you get a new version) and the definition of `Status'
> changes to [...]
> The IDL binding would produce wrong code, but the Green Card
> binding would still be correct.  Right?  Or do I miss something?

The Green Card binding will definitely be correct, but AFAIK the IDL
binding will be not. This was one of my main motivations for preferring
Green Card to H/Direct. To the IDL wizards: Is there a *simple* way to
ensure consistency between header files and IDL sources, i.e. without
perl/m4/awk/...? This is very important when you can't rely on a
portable mapping of enumeration types to int. My usual example: AFAIK,
in OpenGL there's no guarantee that your GL_xyz identifier is mapped
to a certain int (via enum or cpp).

BTW, both Green Card and IDL lose when an enumeration type gets an
additional value, e.g. EXIT_WITH_LIMITED_SUCCESS  :-)

And another point: I doubt that it is very feasible to automatically
generate either Green Card sources or IDL from .h-files. Almost none
of the header files I have seen use types very well, e.g. OpenGL uses
GLenum for almost every enumeration type around, unistd.h uses int for
the same purpose, [ list could be continued lazily... ]

Cheers,
   Sven
-- 
Sven PanneTel.: +49/89/2178-2235
LMU, Institut fuer Informatik FAX : +49/89/2178-2211
LFE Programmier- und Modellierungssprachen  Oettingenstr. 67
mailto:[EMAIL PROTECTED]D-80538 Muenchen
http://www.pms.informatik.uni-muenchen.de/mitarbeiter/panne



Re: Xlib IDL for H/Direct?

1999-03-30 Thread Sven Panne

"Sigbjorn Finne (Intl Vendor)" wrote:
> Manuel does highlight a problem, but it's an example of Bad Practice
> on the part of the library provider - rejigging the ordering and mapping
> of enumeration tags is a no-no if you care about backward compatibility.

But there are libraries out there which guarantee only source level
compatibility, and changing the mapping is absolutely valid in those
cases. I really don't advocate random re-mappings, but those things exist
in real life (tm).

> [Do GL enums vary between implementations? I'm surprised]

I was, too, when I first read this (in news:comp.graphics.api.opengl,
I think). Currently it is quite probable that newer implementations
agree on this, but there is no guarantee.

> [...] HDirect could generate output which delayed the binding of enum
> tags to values until the Haskell/C stubs are compiled, if this is a
> real problem. [...]

Following Wadler's Law of Language Design (available at
http://www-i2.informatik.rwth-aachen.de/~hanus/curry/listarchive/0017.html)
we should first agree on the syntax before talking about semantics :-),
so here's my first shot, re-using litlits:

   typedef enum { 
  ExitFailure = ``EXIT_FAILURE'',
  ExitSuccess = ``EXIT_SUCCESS''
   } Status;

or even better:   (almost like Green Card :-)

   typedef enum [useValuesFromHeaderAndDoCunningNameMangling] { 
  EXIT_FAILURE, EXIT_SUCCESS
   } Status;

Would this be hard to integrate?

Cheers,
   Sven
-- 
Sven PanneTel.: +49/89/2178-2235
LMU, Institut fuer Informatik FAX : +49/89/2178-2211
LFE Programmier- und Modellierungssprachen  Oettingenstr. 67
mailto:[EMAIL PROTECTED]D-80538 Muenchen
http://www.pms.informatik.uni-muenchen.de/mitarbeiter/panne



RE: Xlib IDL for H/Direct?

1999-03-30 Thread Sigbjorn Finne (Intl Vendor)


Sven Panne <[EMAIL PROTECTED]> writes: 
> 
 
> 
> > [...] HDirect could generate output which delayed the 
> > binding of enum tags to values until the Haskell/C stubs are
> > compiled, if this is a real problem. [...]
> 
  ...
> 
>  typedef enum { 
> ExitFailure = ``EXIT_FAILURE'',
> ExitSuccess = ``EXIT_SUCCESS''
>  } Status;
> 
> or even better:   (almost like Green Card :-)
> 
>typedef enum [useValuesFromHeaderAndDoCunningNameMangling] { 
>   EXIT_FAILURE, EXIT_SUCCESS
>} Status;

I was imagining the latter together with a command-line switch; I'm
not sure if a new custom attribute is warranted for this.

Oh, and you want name mangling as well. Hadn't thought of that, but
could always support a [naming_scheme(..)] attribute. Will see what
I can do.

--sigbjorn



RE: Xlib IDL for H/Direct?

1999-03-31 Thread Manuel M. T. Chakravarty

"Sigbjorn Finne (Intl Vendor)" <[EMAIL PROTECTED]> wrote,

[...]
> Having a .h -> .idl route would be helpful (at least until .idl has
> supplanted the use .h as a means to specify libs ;-), but I'm probably
> not going to invest any more time developing HDirect (or GreenCard),
> so if anyone feels the itch, go for it!

Oh, really?  That's bad news, I guess.  What will be your
new "project"?

Manuel



RE: Xlib IDL for H/Direct?

1999-03-30 Thread Sigbjorn Finne (Intl Vendor)


Sven Panne <[EMAIL PROTECTED]> writes: 
> 
> "Manuel M. T. Chakravarty" wrote:
> > Isn't there still a difference?  When the C-library changes
> > (ie, you get a new version) and the definition of `Status'
> > changes to [...]
> > The IDL binding would produce wrong code, but the Green Card
> > binding would still be correct.  Right?  Or do I miss something?
> 
> The Green Card binding will definitely be correct, but AFAIK the IDL
> binding will be not. This was one of my main motivations for 
> preferring Green Card to H/Direct. To the IDL wizards: Is there a
> *simple* way to ensure consistency between header files and IDL
> sources, i.e. without perl/m4/awk/...? This is very important when
> you can't rely on a portable mapping of enumeration types to int.
> My usual example: AFAIK, in OpenGL there's no guarantee that your
> GL_xyz identifier is mapped to a certain int (via enum or cpp).
> 

Manuel does highlight a problem, but it's an example of Bad Practice
on the part of the library provider - rejigging the ordering and mapping
of enumeration tags is a no-no if you care about backward compatibility.
[Do GL enums vary between implementations? I'm surprised]

Extending them 'at the end' is acceptable, and what most sane people
seem to be doing. However, since both GC and HDirect doesn't work on
the .h file directly, they're, as you say, unlikely to pick up such a
change :)

HDirect could generate output which delayed the binding of enum tags
to values until the Haskell/C stubs are compiled, if this is a
real problem.

Having a .h -> .idl route would be helpful (at least until .idl has
supplanted the use .h as a means to specify libs ;-), but I'm probably
not going to invest any more time developing HDirect (or GreenCard),
so if anyone feels the itch, go for it!

--sigbjorn



Re: Xlib IDL for H/Direct?

1999-03-31 Thread Manuel M. T. Chakravarty

[EMAIL PROTECTED] (Carl R. Witty) wrote,

> Sven Panne <[EMAIL PROTECTED]> writes:
> 
> > The Green Card binding will definitely be correct, but AFAIK the IDL
> > binding will be not. This was one of my main motivations for preferring
> > Green Card to H/Direct. To the IDL wizards: Is there a *simple* way to
> > ensure consistency between header files and IDL sources, i.e. without
> > perl/m4/awk/...?
> 
> (Disclaimer: I'm not an IDL wizard.)
> 
> In a sense, there is a way to ensure consistency between header files
> and IDL sources: generate the header files from the IDL.  This should
> work fine for projects where you're maintaining the C side yourself
> (so you can decide to move to IDL for the "master"), but is obviously
> going to be quite difficult for externally maintained libraries.  (I
> could imagine Gtk moving in that direction, though...I wonder if
> they'd be receptive to such a proposal?)

I am not sure whether that would work for GTK+.  The reason
is that GTK+'s .h files contain a lot of "internal"
interfaces, ie, routines and data structures, which should
not be used by applications building on GTK+.  Furthermore,
GTK+ makes heavy use of macros and I am not sure how you
would represent them in an IDL.

Manuel



Re: Xlib IDL for H/Direct?

1999-03-31 Thread Manuel M. T. Chakravarty

Sven Panne <[EMAIL PROTECTED]> wrote,

> "Manuel M. T. Chakravarty" wrote:
> > Isn't there still a difference?  When the C-library changes
> > (ie, you get a new version) and the definition of `Status'
> > changes to [...]
> > The IDL binding would produce wrong code, but the Green Card
> > binding would still be correct.  Right?  Or do I miss something?
> 
> The Green Card binding will definitely be correct, but AFAIK the IDL
> binding will be not. This was one of my main motivations for preferring
> Green Card to H/Direct. To the IDL wizards: Is there a *simple* way to
> ensure consistency between header files and IDL sources, i.e. without
> perl/m4/awk/...? This is very important when you can't rely on a
> portable mapping of enumeration types to int. My usual example: AFAIK,
> in OpenGL there's no guarantee that your GL_xyz identifier is mapped
> to a certain int (via enum or cpp).
> 
> BTW, both Green Card and IDL lose when an enumeration type gets an
> additional value, e.g. EXIT_WITH_LIMITED_SUCCESS  :-)

I think, I may have a solution that does even the latter :-)

> And another point: I doubt that it is very feasible to automatically
> generate either Green Card sources or IDL from .h-files. Almost none
> of the header files I have seen use types very well, e.g. OpenGL uses
> GLenum for almost every enumeration type around, unistd.h uses int for
> the same purpose, [ list could be continued lazily... ]

The basic idea is to combine information from the C header
file with high-level type information from Haskell.  And do
so with a "slim" tool (ie, less "new language" than Green
Card or an IDL).  The main purpose of the tool would be to
Haskelize existing C libraries (ie, it is much less
ambitious than HDirect).  But let's wait and see whether it
works the way I hope...

Manuel