> 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