[Haskell-cafe] Re: Complex C99 type in Foreign

Aaron Denney wnoise at ofb.net
Fri Feb 13 16:16:57 EST 2009


On 2009-02-03, Maurí­cio <briqueabraque at yahoo.com> wrote:
>>>>> Are there plans to include C99 'complex' type
>>>>> in Foreign, maybe as CFloatComplex, CDoubleComplex
>
>>>> A separate library for new types to add to Foreign would be the easiest
>>>> way forward. Just put the foreign-c99 package on Hackage?
>
>>> (...) I could actually have some
>>> arbitrary sized parameter as argument to a function
>>> or as a return value (and not its pointer), what
>>> did I saw wrong? I understand only Foreign.C.C*
>>> types or forall a. => Foreign.Ptr.Ptr a can be used
>>> like that.
>> 
>> Oh, you mean you need to teach the compiler about unboxed complex types?
>> 
>
> I'm sorry, maybe I didn't understand you well. Are
> you saying that I could get this 'CComplex' type using
> unboxed types and other things already available?

Yes, because the C standard guarantees that a complex <type> is
stored as <type>[2].

I have been using the following, for binding to FFTW:

-----------------------------------------------------------------------------
-- |
-- Module      : CComplex
-- Copyright   : (c) Aaron Denney 2004
-- License     : BSD, 2-clause
-- 
-- Maintainer  : wnoise-haskell at ofb.net
-- Stability   : experimental
-- Portability : FFI
--
-- Aims to provide "CComplex a" parameterized type representing C99's
-- complex types and provide Storable instances for both it and
-- Haskell's Complex a types.  Note that C99 can parameterize over
-- integral types -- I think it's a mistake for Complex to not be
-- defined over all Real types.
--
-- For efficiency of common use, we use C's representation for easy
-- conversion.  So, we can be sloppy and use Complex CDouble instead of
-- CComplex CDouble.  In fact, for now CComplex is merely a type synonym
-- for Complex.
--
-- Will hopefully become obsolete when the FFI is revised to include the
-- complex types of C99.
------------------------------------------------------------------------

module CComplex (CComplex) where
import Complex (Complex(..))
import Foreign.Ptr (castPtr)
import Foreign.Storable

-- C 99 specifies that a variable v of type complex t is stored as
-- t v [2], with v[0] the real part and v[1] the imaginary part.
-- elem off and byte off are defaulted, but perhaps shouldn't be,
-- for efficiency.

instance (RealFloat a, Storable a) => Storable (Complex a) where
    sizeOf x    = 2 * sizeOf (f x)
    alignment x = alignment  (f x)
    poke      x (a :+ b) = do let y = castPtr x
                              poke y a
                              pokeElemOff y 1 b
    peek      x          = do let y = castPtr x
                              a <- peek y
                              b <- peekElemOff y 1
                              return (a :+ b)

type CComplex a = Complex a

f :: Complex a -> a
f _ = undefined                                                         

------------------------------------------------
HTH.

-- 
Aaron Denney
-><-



More information about the Haskell-Cafe mailing list