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

2009-02-16 Thread Aaron Denney
On 2009-02-14, Maurí­cio briqueabra...@yahoo.com wrote:
 The way you wrote CComplex a, is it possible to write

 foreign import ccall somename somename
:: CComplex CDouble - IO CComplex CDouble

Ah, no, I'm afraid not,  I misunderstood what you wanted.  You do indeed
need to go through CPtr (CComplex CDouble) with this scheme.  I think
having direct access at this level requires modifying the compiler.  The
FFI spec really does need to be updated to C99.

-- 
Aaron Denney
--

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2009-02-13 Thread Aaron Denney
On 2009-02-03, Maurí­cio briqueabra...@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-hask...@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
--

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2009-02-13 Thread Maurí­cio

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:


The way you wrote CComplex a, is it possible to write

foreign import ccall somename somename
  :: CComplex CDouble - IO CComplex CDouble

?

Thanks,
Maurício

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2009-02-02 Thread Maurí­cio

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?

Maurício

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2009-02-01 Thread Maurí­cio

Are there plans to include C99 'complex' type
in Foreign, maybe as CFloatComplex, CDoubleComplex
and CLongDoubleComplex? This seems an easy addition
to the standard and would allow binding of a few
interesting libraries, like GSL.


A separate library for new types to add to Foreign would be the easiest
way forward. Just put the foreign-c99 package on Hackage?


As far as I know, this is not possible. (I tried for
a long time to do that, actually, until I reallized
it could not be done.)

If it's not true, i.e., 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.

Maurício

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2009-02-01 Thread Don Stewart
briqueabraque:
 Are there plans to include C99 'complex' type
 in Foreign, maybe as CFloatComplex, CDoubleComplex
 and CLongDoubleComplex? This seems an easy addition
 to the standard and would allow binding of a few
 interesting libraries, like GSL.
 
 A separate library for new types to add to Foreign would be the easiest
 way forward. Just put the foreign-c99 package on Hackage?
 
 As far as I know, this is not possible. (I tried for
 a long time to do that, actually, until I reallized
 it could not be done.)
 
 If it's not true, i.e., 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?

-- Don
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2009-02-01 Thread Maurí­cio

Are there plans to include C99 'complex' type
in Foreign, maybe as CFloatComplex, CDoubleComplex
and CLongDoubleComplex? (...)



A separate library for new types to add to Foreign would be the easiest
way forward. (...)



If it's not true, i.e., 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? (...)



Oh, you mean you need to teach the compiler about

 unboxed complex types?

I think so. Take this, for instance:


#include complex.h
double complex ccos(double complex z);
float complex ccosf(float complex z);
long double complex ccosl(long double complex z);


To bind to ccos* functions I believe I would need
a native CComplex. The GSL numeric library also
makes use of something like that, although it
defines its own 'complex' structure.

I'm writing a binding to the standard C library,
and at the same time collecting a list of standard
types that could be usefull in Foreign. I'm thinking
about writing a ticket to ask for inclusion of a few
of them. 'int32_t' and 'int64_t' as, say, CInt32 and
CInt64 could be nice for portability.

Maurício

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe