Proposal - Foreign enum support

Carter Schonwald carter.schonwald at gmail.com
Sat Apr 19 14:04:42 UTC 2014


Have you considered a type class and new types ? :-)

On Saturday, April 19, 2014, Merijn Verstraaten <merijn at inconsistent.nl>
wrote:

> After some thinking it'd be possible to implement this using a quasiquoter
> and pattern synonyms, however you'd lose the ability to get exhaustiveness
> checks for the pattern synonyms. Would people be equally opposed to the
> idea of defining a "closed" set of synonyms? That is a user defines a set
> of synonyms 'Foo', 'Bar', 'Baz' and a function defined on all three is
> considered exhaustive regardless of the underlying type. Otherwise using
> synonyms as abstract constructors for such enum types will result in rather
> confusing warning of functions not being exhaustively defined.
>
> Cheers,
> Merijn
>
> On Apr 17, 2014, at 18:06 , John Lato wrote:
>
> I wouldn't be keen on adding such a specific feature to the language
> either.  Another concern is that this proposal doesn't seem to address a
> very common use case for C enums, bit vectors.  IMHO any FFI proposal for
> working with C enums should take that idiom into account.
> On Apr 17, 2014 7:19 AM, "Merijn Verstraaten" <merijn at inconsistent.nl>
> wrote:
>
> Cross-post to haskell-prime in case there's any interest for including
> this into the report's FFI specification.
>
> Proposal - Foreign enum support
> ===============================
>
> At the moment the FFI does not have a convenient way with interacting enums
> (whether proper enums or CPP defines) in C (like languages). Both enums
> and CPP
> defined enums are major parts of large C APIs and they are thus crucial to
> writing foreign bindings. A few examples:
>
> SDL_image defines the following enum:
>
>     typedef enum {
>         IMG_INIT_JPG = 0x00000001,
>         IMG_INIT_PNG = 0x00000002,
>         IMG_INIT_TIF = 0x00000004,
>         IMG_INIT_WEBP = 0x00000008
>     } IMG_InitFlags;
>
> OpenCL specifies the following typedefs + CPP defined enum:
>
>     typedef uint32_t  cl_uint     __attribute__((aligned(4)));
>     typedef cl_uint   cl_platform_info;
>
>     /* cl_platform_info */
>     #define CL_PLATFORM_PROFILE                         0x0900
>     #define CL_PLATFORM_VERSION                         0x0901
>     #define CL_PLATFORM_NAME                            0x0902
>     #define CL_PLATFORM_VENDOR                          0x0903
>     #define CL_PLATFORM_EXTENSIONS                      0x0904
>
> OpenCL functions will return the above CPP defines as return values of type
> cl_platform_info.
>
> Current Solutions
> -----------------
>
> In many cases someone wrapping such a C library would like to expose these
> enums as a simple sum type as this has several benefits: type safety, the
> ability to use haskell constructors for pattern matching, exhaustiveness
> checks.
>
> Currently the GHC FFI, as specified by Haskell2010, only marshalls a small
> set
> of foreign types and newtypes with exposed constructors of these types. As
> such
> there seem two approaches to wrap these enums:
>
>  1. Implement an ADT representing the enum and write a manual conversion
>     function between the ADT and the corresponding C type (e.g. CInt ->
> Foo and
>     Foo -> CInt).
>
>  2. Use a tool like c2hs to automatically generate the ADT and conversion
>     function.
>
> In both cases the foreign functions are imported using the corresponding C
> type
> in their signature (reducing type safety) and the user is forced write
> trivial
> wrappers for every imported function to convert the ADT to the relevant C
> type
> and back.
>
> This is both tedious to write and costly in terms of code produced, in
> case of
> c2hs one calls "toEnum . fromIntegral" and "fromIntegral . fromEnum" for
> every
> argument/result even though this could trivially be a no-op.
>
> Worse, since c2hs uses the Enum class for it's conversion to/from C types
> it
> generates Enum instances like:
>
>     instance Enum Foo where
>         fromEnum Bar = 1
>         fromEnum Baz = 1337
>
>         toEnum 1 = Bar
>         toEnum 1337 = Baz
>         toEnum unmatched = error ("PlatformInfo.toEnum: Cannot match " ++
> show unmatched)
>
> Since succ/pred and enumFromTo's default implementations assume enums
> convert
> to continuous sequence of Int this means the default generated enum
> instances
> crash. This problem could be overcome by making c2hs' code generation
> smarter,
> but this does not eliminate the tediousness of wrapping all foreign
> imported
> functions with marshalling wrappers, NOR does it eliminate the overhead of
> all
> this useless marshalling.
>
> Proposal
> --------
>
> Add a new foreign construct for enums, the syntax I propose below is rather
> ugly and ambiguous and thereforeopen to bikeshedding, but I prefer
> explaining
> based on a concrete example.
>
>     foreign enum CInt as Foo where
>         Bar = 1
>         Baz
>         Quux = 1337
>         Xyzzy = _
>
> This would introduce a new type 'Foo' with semantics approximately
> equivalent
> too "newtype Foo = Foo CInt" plus the pattern synonyms "pattern Bar = Foo
> 1;
> pattern Baz = 2; pattern Quux = 1337; pattern Xyzzy = Foo _".
>
> Explicit listing of the value corresponding to a constructor should be
> optional, missing values should just increment by one from the previous
> (like
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/ghc-devs/attachments/20140419/780c8779/attachment.html>


More information about the ghc-devs mailing list