Re: [Haskell-cafe] Audio signal processing in Haskell

2004-04-03 Thread David Roundy
On Sat, Apr 03, 2004 at 07:04:18PM +0200, Henning Thielemann wrote:
> 
>  What is the most promising strategy to speed up the computation without
> loosing the elegance of Haskell's lists?
>  1. Upgrading GHC from 6.0 to the current version?
>  2. Use of simplification rules? How can I find out what new rules may be
> useful? The several dumps that GHC can generate are a bit hard to
> understand.  :-( Is there some more detailed information about what rules
> GHC already applies than what one can get with -ddump-simpl-stats and
> -ddump-rules?
>  3. More strictness? Is a custom list structure with strict entries and
> maybe with only one constructor (thus always infinite) a considerable
> alternative? This would disallow the use of lots of functions that deal
> with lists, including State monad functions. 
>  4. A list of arrays? Then signal processes with feedback like an echo are
> much more difficult.

Try using profiling to see where exactly your time is being spent, and then
perhaps posting back here with the problematic function.  Also, of course,
looking at scaling is key, make you know the scaling of each function
(i.e. how many times it gets called), and that there isn't anything you can
do to fix the scaling.

Lists are slow, and laziness is slow, but on the other hand, computers are
fast, so before trying any of 1-4 (all of which seem likely to uglify your
code a bit) I'd try to see if you can fix up the algorithms in your code to
be more efficient.  I assume that if your highest priority was writing
blindingly fast code, you'd be writing in C.  I guess one thing you could
try (if you haven't already done so) is writing a simple program that just
reads and writes and does nothing in between (except convert to a lazy
list), to see how slow that is.

Is laziness really an important issue? Are you interested in it mostly just
for memory consumption reasons, to avoid holding an entire file in memory,
or are you perhaps thinking to make the code work with real-time input?

If you decide you need something faster (but still pretty) and don't need
laziness and can fit your data in memory, I think an infinite array might
be the way to go.  You could pretty easily create a wrapper around a UArray
or a ForeignPtr which would pad it with zeros in both plus and minus
infinity directions.  Then you could also create a "time offset" function
that shifts an array by a given amount (without making a copy), and could
probably do most of what you'd like to do.

I imagine something like

data InfiniteArray = IA !(ForeignPtr Int16) !Int !Int

(!) :: InfiniteArray -> Int -> Int16
(IA for_ptr start_index end_index the_offset) ! i
| i < start_index = 0
| i > end_index = 0
| otherwise = unsafePerformIO $ withForeignPtr for_ptr $
  \p -> peekElemOff p (the_offset + i)


createIA :: Int -> (Ptr Word16 -> IO ()) -> InfiniteArray
createIA length write_ptr =
   unsafePerformIO $ do fp <- mallocForeignPtr length
withForeignPtr fp $ \p -> write_ptr p
return $ IA fp 0 (l-1) 0

offsetIA :: Int -> InfiniteArray -> InfiniteArray
offsetIA offset_by (IA start_index end_index the_offset)
= IA (start_index + offset_by) (end_index + offset_by)
 (the_offset - offset_by)

Note that I only used ForeignPtr's because I'm familiar with them, and
haven't used UArrays much.  Unless you need to use FFI, you're probably
better off with UArrays.  On the other hand, with ForeignPtr's you leave
yourself open to the possibility of calling an FFT program through the FFI,
and you definitely *don't* want to write an FFT in haskell.
-- 
David Roundy
http://www.abridgegame.org
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Audio signal processing in Haskell

2004-04-03 Thread Henning Thielemann

As I can see a question similar to mine was already raised here:
 http://www.haskell.org/pipermail/glasgow-haskell-users/2004-February/006305.html

 I also encountered the elegance that Haskell's laziness provides for
signal processing. I use lists for the signals. With help of Haskore I put
together a small song and it needed 5 minutes for rendering the quite
simple music of about 30 seconds. Don't care about the exact numbers but I
find it rather slow. 
 What is the most promising strategy to speed up the computation without
loosing the elegance of Haskell's lists?
 1. Upgrading GHC from 6.0 to the current version?
 2. Use of simplification rules? How can I find out what new rules may be
useful? The several dumps that GHC can generate are a bit hard to
understand.  :-( Is there some more detailed information about what rules
GHC already applies than what one can get with -ddump-simpl-stats and
-ddump-rules?
 3. More strictness? Is a custom list structure with strict entries and
maybe with only one constructor (thus always infinite) a considerable
alternative? This would disallow the use of lots of functions that deal
with lists, including State monad functions. 
 4. A list of arrays? Then signal processes with feedback like an echo are
much more difficult.



___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Context for type parameters of type constructors

2004-04-03 Thread Dylan Thurston
On Sat, Apr 03, 2004 at 01:35:44PM +0200, Henning Thielemann wrote:
>   (I like to omit  -fallow-undecidable-instances
>before knowing what it means)

There's a nice section in the GHC user's manual on it.  I can't add
anything to that.

> > -- a classical linear space
> > class VectorSpace v a where
> >zero  :: v
> >add   :: v -> v -> v
> >scale :: a -> v -> v

You might want to add a functional dependency, if you only have one
type of scalars per vertor space:

> class VectorSpace v a | v -> awhere
>zero  :: v
>add   :: v -> v -> v
>scale :: a -> v -> v

But then again, you might not.

> > instance Num a => VectorSpace a a where
> >zero  = 0
> >add   = (+)
> >scale = (*)
> 
> Here the compiler complains the first time:
> 
> VectorSpace.lhs:27:
> Illegal instance declaration for `VectorSpace a a'
> (There must be at least one non-type-variable in the instance head
>  Use -fallow-undecidable-instances to permit this)
> In the instance declaration for `VectorSpace a a'

Well, you know how to fix this...

Another way to fix it is to add a dummy type constructor:

> newtype Vector a = Vector a
>
> instance Num a => VectorSpace (Vector a) a

Later:
> > instance Num a => VectorSpace [a] a where

By the way, depending how you resolve the issue above, you might want
instead

> instance (RealFloat a, VectorSpace b a) => VectorSpace [b] a where
> ...


> Now I introduce a new datatype for a vector valued quantity.
> The 'show' function in this simplified example
> may show the vector with the magnitude separated
> from the vector components.
> ...
> The problem which arises here is that the type 'a' is used for
> internal purposes of 'show' only. Thus the compiler can't decide
> which instance of 'Normed' to use if I call 'show':

This is exactly what is fixed by adding the functional dependency
above.

Alternatively, if you want to consider varying the scalars, you can
add 'a' as a dummy type variable to 'Quantity':

> data Quantity v a = Quantity v
>
> instance (Show v, Fractional a, Normed v a) =>
> Show (Quantity v a) where
>show (Quantity v) =
>let nv::a = norm v
>in  (show (scale (1/nv) v)) ++ "*" ++
>(show nv)

GHC still won't accept this without prompting, but now at least you
can provide a complete type:

*VectorSpace> show (Quantity [1,2,3] :: Quantity [Double] Double)
"[0.1,0.,0.5]*6.0"

Note that this makes sense semantically: if you have a vector space
over both, say, the reals and the complexes, you need to know which
base field to work over when you normalize.

> So I tried the approach which is more similar
> to what I tried before with a single-parameter type class:
> I use a type constructor 'v' instead of a vector type 'v'
> ...

> > data QuantityC v a = QuantityC (v a)
> >
> > instance (Fractional a, NormedC v a, Show (v a)) =>
> > Show (QuantityC v a) where
> >show (QuantityC v) =
> >let nv = normC v
> >in  (show (scaleC (1/nv) v)) ++ "*" ++
> >(show nv)
> 
> It lead the compiler eventually fail with:
> VectorSpace.lhs:138:
> Non-type variables in constraint: Show (v a)
> (Use -fallow-undecidable-instances to permit this)
> In the context: (Fractional a, NormedC v a, Show (v a))
> While checking the context of an instance declaration
> In the instance declaration for `Show (QuantityC v a)'

Hmm, I don't know how to fix up this version.

Peace,
Dylan


signature.asc
Description: Digital signature
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Functional Programming and AI

2004-04-03 Thread GAYLE, Orrett Orville
I was wondering if I could be directed to resources for Artificial 
Inteligence where Hakell (or any other functional language for that 
matter) is the language of implementation. I am fairly new to the feild 
and that should be a concideration when sending the  listings.

Thanks in advance. 
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Context for type parameters of type constructors

2004-04-03 Thread Henning Thielemann

the next lap ...

On Tue, 30 Mar 2004, Dylan Thurston wrote:

> I recommend you use multi-parameter type classes, with a type of the
> scalars and the type of the vectors.  For the method you're using, you
> need to add a 'Num a' context.  You say that you 'cannot catch all
> requirements that instances may need', but certainly any instance will
> need that context. 


Following your advice I tried to solve the problem
with a multi-parameter type classes.
Btw. I need this stuff for computations with physical values,
i.e. numeric values equipped with physical units.
Pure computation with physical values is no problem at all
only converting the values to strings is what causes all the trouble!

I compiled this text with
 ghc -fglasgow-exts -c VectorSpace.lhs
  (I like to omit  -fallow-undecidable-instances
   before knowing what it means)

> module VectorSpace
>where
>
> import Data.Complex

Here is the new vector space class.
Now 'v' is the vector type
and 'a' is a compliant scalar type.

> -- a classical linear space
> class VectorSpace v a where
>zero  :: v
>add   :: v -> v -> v
>scale :: a -> v -> v
>
> instance Num a => VectorSpace a a where
>zero  = 0
>add   = (+)
>scale = (*)

Here the compiler complains the first time:

VectorSpace.lhs:27:
Illegal instance declaration for `VectorSpace a a'
(There must be at least one non-type-variable in the instance head
 Use -fallow-undecidable-instances to permit this)
In the instance declaration for `VectorSpace a a'

> instance RealFloat a => VectorSpace (Complex a) a where
>zero   = 0
>add= (+)
>scale s (x:+y) = (s*x) :+ (s*y)
>
> instance Num a => VectorSpace [a] a where
>zero= repeat 0
>add = zipWith (+)
>scale s = map (s*)
>
> instance Num a => VectorSpace (b -> a) a where
>zero  _ = 0
>add   f g x = (f x) + (g x)
>scale s f x = s*(f x)


To stay conform to mathematical systematics
I separated the definition of the norm
from the 'VectorSpace' definition.

> -- a vector space equipped with a norm
> class VectorSpace v a => Normed v a where
>norm :: v -> a
>
> instance Num a => Normed a a where
>norm = abs
>
> instance RealFloat a => Normed (Complex a) a where
>norm = magnitude
>
> instance Num a => Normed [a] a where
>-- fails for infinite lists
>norm = sum.(map abs)


Now I introduce a new datatype for a vector valued quantity.
The 'show' function in this simplified example
may show the vector with the magnitude separated
from the vector components.

> data Quantity v = Quantity v
>
> instance (Show v, Fractional a, Normed v a) =>
> Show (Quantity v) where
>show (Quantity v) =
>let nv::a = norm v
>in  (show (scale (1/nv) v)) ++ "*" ++
>(show nv)

The problem which arises here is that the type 'a'
is used for internal purposes of 'show' only.
Thus the compiler can't decide which instance of 'Normed'
to use if I call 'show':

Prelude VectorSpace> show (Quantity [1,2,3])

:1:
No instance for (Normed [t] a)
  arising from use of `show' at :1
In the definition of `it': it = show (Quantity [1, 2, 3])




So I tried the approach which is more similar
to what I tried before with a single-parameter type class:
I use a type constructor 'v'
instead of a vector type 'v'
but now by the two-parameter type class
I mention the type 'a' explicitly
which allows for context restrictions
on instantation later.

> class VectorSpaceC v a where
>zeroC  :: v a
>addC   :: v a -> v a -> v a
>scaleC :: a -> v a -> v a

One consequence is now that I cannot use
the scalar type 'a' as vector type, too.
Instead I need some type constructor 'Identity'
which I can make an instance of class 'VectorSpace'.
So let's immediately switch to the complex numbers.

> instance RealFloat a => VectorSpaceC Complex a where
>zeroC  = 0
>addC   = (+)
>scaleC s (x:+y) = (s*x) :+ (s*y)
>
> class VectorSpaceC v a => NormedC v a where
>normC :: v a -> a
>
> instance RealFloat a => NormedC Complex a where
>normC = magnitude

But the 'Show' instance causes new trouble:

> data QuantityC v a = QuantityC (v a)
>
> instance (Fractional a, NormedC v a, Show (v a)) =>
> Show (QuantityC v a) where
>show (QuantityC v) =
>let nv = normC v
>in  (show (scaleC (1/nv) v)) ++ "*" ++
>(show nv)

It lead the compiler eventually fail with:
VectorSpace.lhs:138:
Non-type variables in constraint: Show (v a)
(Use -fallow-undecidable-instances to permit this)
In the context: (Fractional a, NormedC v a, Show (v a))
While checking the context of an instance declaration
In the instance declaration for `Show (QuantityC v a)'


Does exist a clean solution for the problem at all?


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe