[Numeric] ix-shapable vs. fft

Henning Thielemann lemming at henning-thielemann.de
Thu Jul 23 08:52:08 UTC 2015


I like to discuss some issues about the Haskell package 'fft' package with 
you.

I am thinking for long about ix-shapable and its use in 'fft'. I find it 
pretty counter-intuitive that FFT.dftRC transforms the outermost dimension 
of an array and that the dimension list passed to FFT.dftRCN counts from 
the outermost to the innermost dimension. I guess that the reason is how 
Shapable methods convert between tuples and lists. In a tuple (a,b,c), 'a' 
is the zeroth element of the tuple but as an index it counts the outermost 
dimension. Shapable methods 'sShape' and 'sBounds' convert that tuple to 
the list [a,b,c] and back. Of course, [a,b,c]!!0 == a.

With the working of Shapable in mind, the current convention of counting 
dimensions in FFT.dftRCN makes sense but most of the time I only use a 
certain tuple type like (Int,Int,Int) and do not care about its Shapable 
instance. I do not spell Shapable in the source code, at all.

Other problems are: Shapable instances are overly strict in that they 
allow only tuples that consist entirely of Ints. But e.g. it would be no 
problem to have the index type (Char, Int, Integer) if we only transform 
the middle dimension. Additionally the current Shapable instances for 
tuples require FlexibleInstances, which I find ugly and unnecessary. On 
the other hand FFT.dftRCN lacks type safety: You can easily specify 
non-existent dimensions for transformation.

The last problem can be overcome by replacing the list of transform 
dimensions by a Bool tuple. How about a call like this:
    FFT.dftRCN (False, True, False) array3d
?

A fine solution is not as simple as a tuple of Bools, but here is 
something close to it:

~~~~
import Data.Complex (Complex)
import Data.Monoid (Monoid, (<>))


data IndexMagic = InsertMagicHere
data Dim ix = Dim IndexMagic

instance Monoid IndexMagic where


keep :: Dim ix
keep = Dim InsertMagicHere

trans :: Dim Int
trans = Dim InsertMagicHere

mask2 :: Dim ix0 -> Dim ix1 -> Dim (ix0,ix1)
mask2 (Dim op0) (Dim op1) = Dim (op0 <> op1)

mask3 :: Dim ix0 -> Dim ix1 -> Dim ix2 -> Dim (ix0,ix1,ix2)
mask3 (Dim op0) (Dim op1) (Dim op2) = Dim (op0 <> op1 <> op2)

dftRCN :: Dim i -> array i a -> array i (Complex a)
dftRCN = undefined


example ::
    array (Char, Int, Integer) a ->
    array (Char, Int, Integer) (Complex a)
example = dftRCN (mask3 keep trans keep)
~~~~


IndexMagic would be a dictionary of functions for doing the necessary 
index processing. With this solution we would not need a Shapable class 
nor a ix-shapable package, and we stay Haskell 98.

For some time I prefered a solution using nested Int dimensions as in 
'repa' and 'accelerate'. But maybe the tuple approach sketched above isn't 
so bad.

Since the 'fft' package is in use for a rather long time now I hesitate to 
change something. I will certainly start a new module providing the same 
function names with new types.


More information about the Numeric mailing list