trying to go from FFT type to Vector.Storable

Hi, I'm using the FFT package (the FFTW bindings), and for a complex FFT I get back : (FFTWReal r, Ix i, Shapable i) => CArray i (Complex r) -> CArray i (Complex r) at first I thought I could use elems to get to a list and then do Vector.Storable.fromList to get back to a Vector.Storable. Unfortunately r is FFTWReal so i need to map over the returned list and get a haskell Double back from that. FFTWReal maps to RealFloat which i found, but i haven't found anything that will take a RealFloat and give me a Double. Was hoping someone might know how to do that, or maybe have a little cleaner way to get from the FFT data type over to Vector. Thanks. Brian

On Tue, 12 May 2015 05:50:26 +0200,
(FFTWReal r, Ix i, Shapable i) => CArray i (Complex r) -> CArray i (Complex r) : FFTWReal maps to RealFloat which i found, but i haven't found anything that will take a RealFloat and give me a Double.
L.S., You could use something like: toDouble :: FFTWReal r => r -> Double toDouble = id Or add the type of the functions you create to your program. Regards, Henk-Jan van Tuyl -- Folding@home What if you could share your unused computer power to help find a cure? In just 5 minutes you can join the world's biggest networked computer and get us closer sooner. Watch the video. http://folding.stanford.edu/ http://Van.Tuyl.eu/ http://members.chello.nl/hjgtuyl/tourdemonad.html Haskell programming --

On 12/05/15 11:43, Henk-Jan van Tuyl wrote:
You could use something like: toDouble :: FFTWReal r => r -> Double toDouble = id
I don't think this is going to typecheck. You probably had something like this in mind: toDouble :: (forall r . FFTWReal r => r) -> Double toDouble d = d Here's a simpler way to do that: toDouble :: Double -> Double toDouble = id Roman

On 05/11/2015 11:50 PM, briand@aracnet.com wrote:
FFTWReal maps to RealFloat which i found, but i haven't found anything that will take a RealFloat and give me a Double. Double` is `RealFloat`, so it is `Fractional`. Every FFTWReal is a `Real` too, so you can use realToFrac to map from FFTWReal to Double:
fftwRealToDouble :: FFTWReal r => r -> Double fftwRealToDouble = realToFrac Regards. -- Leza Morais Lutonda, Lemol-C http://lemol.github.io 50 Aniversario de la Cujae. Inaugurada por Fidel el 2 de diciembre de 1964 http://cujae.edu.cu

On Tue, 12 May 2015 11:19:48 -0400
Leza Morais Lutonda
On 05/11/2015 11:50 PM, briand@aracnet.com wrote:
FFTWReal maps to RealFloat which i found, but i haven't found anything that will take a RealFloat and give me a Double. Double` is `RealFloat`, so it is `Fractional`. Every FFTWReal is a `Real` too, so you can use realToFrac to map from FFTWReal to Double:
fftwRealToDouble :: FFTWReal r => r -> Double fftwRealToDouble = realToFrac
Regards.
Well what I was _really_ trying to do was to get to a Vector of (Complex Double). Interestingly, the following, where ys is type Vector.Storable (Complex Double), ys_array = listArray (0, V.length ys -1) (V.toList ys) y = V.fromList $ map (\z -> realPart z :+ imagPart z) (elems (dft ys_array)) worked just fine, but it's not obvious to me that it should have. Seems like the realPart/imagPart should have failed to work because the argument is not Complex Double it's Complex FFTWReal, so I should have ended up with (Complex FFTWReal) when I really wanted (Complex Double) and fail. BTW, it seems to me that it would be awfully nice if FFT delivered results as Vectors instead of the Array thingy. It looked to me like V.Storable is something which is supposed to ease the marshalling to and from the C world. Would it be a whole lot of work to change the interface to Vector.Storable ? Among other advantages, it makes interfacing to HMatrix easier. Thanks, Brian

On 05/14/2015 12:51 AM, briand@aracnet.com wrote:
Well what I was_really_ trying to do was to get to a Vector of (Complex Double).
Interestingly, the following, where ys is type Vector.Storable (Complex Double),
ys_array = listArray (0, V.length ys -1) (V.toList ys) y = V.fromList $ map (\z -> realPart z :+ imagPart z) (elems (dft ys_array))
worked just fine, but it's not obvious to me that it should have. Seems like the realPart/imagPart should have failed to work because the argument is not Complex Double it's Complex FFTWReal, so I should have ended up with (Complex FFTWReal) when I really wanted (Complex Double) and fail.
BTW, it seems to me that it would be awfully nice if FFT delivered results as Vectors instead of the Array thingy. It looked to me like V.Storable is something which is supposed to ease the marshalling to and from the C world.
Would it be a whole lot of work to change the interface to Vector.Storable ?
Among other advantages, it makes interfacing to HMatrix easier. Hi Brian,
I think the problem is in the way of seeing the types and type classes. First, the type of `ys` is not `Vector.Storable (Complex Double)`, it is Vector (Complex Double). `FFTWReal` is not a type, it is a type class. It is used as a constraint for types, for example, the type of `dft`: dft :: (Ix i, Shapable i, FFTWReal r) => CArray i (Complex r) -> CArray i (Complex r) this means that the type `r` must be instance o FFTWReal type class. So, the type of `dft ys_array` is `CArray i (Complex Double)`, since the type of `ys_array` is `CArray i (Complex Double)`, that means that the `r` in the type of `dft` is `Double`. So, the `map` is unnecessary. You can try: ``` vectorToArray v = listArray (0, V.length v - 1) (V.toList v) arrayToVector = V.fromList . elems fft :: FFTWReal r => V.Vector (Complex r) -> V.Vector (Complex r) fft = arrayToVector . dft . vectorToArray ``` Hope it can help! -- Leza Morais Lutonda, Lemol-C Electronics & Telecommunications Engineer Software Development and Architecture Enthusiast http://lemol.github.io 50 Aniversario de la Cujae. Inaugurada por Fidel el 2 de diciembre de 1964 http://cujae.edu.cu

On Thu, 14 May 2015 02:31:55 -0400
Leza Morais Lutonda
On 05/14/2015 12:51 AM, briand@aracnet.com wrote: I think the problem is in the way of seeing the types and type classes. First, the type of `ys` is not `Vector.Storable (Complex Double)`, it is Vector (Complex Double).
Well that may be, but when I try to use Vector (Complex Double) with hmatrix it doesn't work. I have to make sure to use/import Vector.Storable. Meanwhile, back at the fft example. import qualified Data.Vector.Storable as V import Data.Complex import Math.FFT(dft) import Math.FFT.Base(FFTWReal) import Data.Array.IArray(elems) import Data.Array.CArray(listArray) vectorToArray v = listArray (0, V.length v - 1) (V.toList v) arrayToVector = V.fromList . elems fft :: FFTWReal r => V.Vector (Complex r) -> V.Vector (Complex r) fft = arrayToVector . dft . vectorToArray And the following error messages are why i get very little done in an evening of haskell hacking. To understand those error messages I'd have to be so good with haskell that I wouldn't actually need those error messages, or so it seems to me. Clearly I have something important to learn about what you are saying about type classes. So I'll stare at this for a few more hours, and try random type assignments until it works. Meanwhile, along the way, I may type up one of Shakespeare's plays... Thanks very much for your help. simple.hs:9:17: No instance for (V.Storable a0) arising from a use of ‘V.fromList’ The type variable ‘a0’ is ambiguous Relevant bindings include arrayToVector :: Data.Array.CArray.Base.CArray Int a0 -> V.Vector a0 (bound at simple.hs:9:1) Note: there are several potential instances: instance V.Storable a => V.Storable (Complex a) -- Defined in ‘Data.Complex’ instance V.Storable GHC.Fingerprint.Type.Fingerprint -- Defined in ‘Foreign.Storable’ instance V.Storable GHC.Int.Int16 -- Defined in ‘Foreign.Storable’ ...plus 18 others In the first argument of ‘(.)’, namely ‘V.fromList’ In the expression: V.fromList . elems In an equation for ‘arrayToVector’: arrayToVector = V.fromList . elems simple.hs:12:7: Couldn't match type ‘a0’ with ‘Complex r’ because type variable ‘r’ would escape its scope This (rigid, skolem) type variable is bound by the type signature for fft :: FFTWReal r => V.Vector (Complex r) -> V.Vector (Complex r) at simple.hs:11:8-65 Expected type: Data.Array.CArray.Base.CArray Int a0 -> V.Vector (Complex r) Actual type: Data.Array.CArray.Base.CArray Int a0 -> V.Vector a0 Relevant bindings include fft :: V.Vector (Complex r) -> V.Vector (Complex r) (bound at simple.hs:12:1) In the first argument of ‘(.)’, namely ‘arrayToVector’ In the expression: arrayToVector . dft . vectorToArray

On Thu, 14 May 2015 02:31:55 -0400
Leza Morais Lutonda
arrayToVector = V.fromList . elems
Success. arrayToVector :: FFTWReal r => CArray Int (Complex r) -> V.Vector (Complex r) is the correct type declaration. It seems that I am too eager to assign Double to places where `r` would work, and it's entirely due to an obviously glaring whole in my understanding of type classes. I kind of thought i understood them, but i obviously don't, no I need to go figure that out. I also need to spend time to understand exactly how that type declaration solved the error messages. Thanks very much for your help, I really appreciate it ! Brian
participants (4)
-
briand@aracnet.com
-
Henk-Jan van Tuyl
-
Leza Morais Lutonda
-
Roman Cheplyaka