Re: [Haskell-cafe] Haskell audio libraries & audio formats

2008-08-24 Thread Henning Thielemann



On Sun, 24 Aug 2008, Eric Kidd wrote:


Greetings, Haskell folks!

I'm working on a toy program for drum synthesis.  This has lead me to
explore the various sound-related libraries in Hackage.  Along the way,
I've learned several things:

 1. There's a lot of Haskell sound libraries, but no agreement on how
to represent buffers of audio data.


In my sound synthesis library
   http://darcs.haskell.org/synthesizer/
 I use mainly two representations:

1. Chunky sequences based on StorableVector. This is for efficient storage 
and functions that need to process data in a non-causal way. They are not 
good for fusion.

   http://darcs.haskell.org/synthesizer/src/Synthesizer/Storable/Signal.hs

2. A Stream like sequences without wrappers. In fact, they are no data 
storages but generator functions equipped with a seed. I use them for 
causal signal processes. I think that most functions needed for drum 
synthesis are causal. By inlining them, many subsequent causal signal 
processes are fused to one.

   http://darcs.haskell.org/synthesizer/src/Synthesizer/State/Signal.hs



 2. Some of the most useful sound libraries aren't listed in Hackage's
"Sound" section, including HCodecs, SDL-mixer and hogg.


my library is also not at Hackage, it's too much experimental currently


 3. The Haskell OpenAL bindings are great, but ALUT has been removed
from MacOS 10.5.  Of course, a pure-Haskell version of ALUT would
be pretty easy to write, and it could be used as a fallback.
 4. '[[a]]' is _not_ a good representation for multi-channel audio
data.  Manipulating even 10 seconds of audio is noticeably slow.


Using the signal representations I mentioned above, I can synthesize some 
songs in realtime. For stereo signals I use Signal (a,a). However, a 
StereoFrame data type with Storable instance might be even better.



 5. HCodecs is probably the best library for reading WAVE files.  It
uses 'DiffUArray Int a' to represent audio data, and not '[[a]]'.
It also supports MIDI and SoundFont, which is quite handy.
 6. YampaSynth looks really cool, and it might be possible to turn it
into a reusable MIDI synthesizer library for use with HCodecs.
This would be extremely useful: it would provide a basis for all
kinds of crazy MIDI-based programming in Haskell.


If you are after realtime synthesis you might also want to look into 
SuperCollider. I posted some code to control SuperCollider via MIDI to 
haskell-art. I can send it to you, if you like.



What would the ideal Haskell sound API look like?  Personally, I would
love to see:

 a. Something like HCodecs's Data.Audio as the basic sound format.
Data.Audio is an array-based API, and it supports converting
between a wide range of common sample formats.  I don't know how
fast this is, but it already exists, and it's used by YampaSynth.
 b. OpenAL for sound playback, with a portable version of ALUT.  This
may require writing a pure-Haskell version of ALUT.


So far I used Sox' play command fed by a pipe with runInteractiveCommand.


Other nice-to-have features might include:

 e. A standard MIDI format, based on either the HCodecs package or the
midi package.  (HCodecs is used by YampaSynth, and the midi package
is used by alsa-midi.)


midi package is mainly used by Haskore


 f. A modular version of YampaSynth which can convert MIDI data
structures into Data.Audio values.

It looks like Haskell could be a really sweet audio programming
environment with just a bit of integration work.  What do folks think?
Are there other libraries I should look at more closely?  Other features
that should be included in an ideal audio API?


What do you mean by 'API'? I think there should not be one library 
handling all kind of music tasks. For interoperability common data 
structures are nice. However, what signal representation concerns, 
I think we need more than one representation, because different 
applications have different needs.




Haskell audio libraries


I have advertised my libraries for years in Haskell-Wiki and HCAR, but it 
seems that people do not look there. :-(





Reading and writing sound files:
 HCodecs: (Audible a) => DiffUArray Int a
 hsndfile: MArray with Float and Double
 HSoundFile: [[Double]]
 ALUT: OpenAL.AL.Buffer
 WAVE: [[Int32]]

Playing sounds:
 OpenAL: Ptr UInt8, Ptr Int16, 1-N channels
 SDL-mixer: ForeignPtr ChunkStruct, ForeignPtr MusicStruct


Sox via pipe, using any data structure which can be written to a file



Sound processing libraries:
 dsp: Array a, [a]
 jack: Operates via mapping functions
   mainMono :: (CFloat -> IO CFloat) -> IO ()
   mainStereo :: ((CFloat, CFloat) -> IO (CFloat, CFloat)) -> IO ()


synthesizer: StorableVector, State, Generic (older: list, fusable list)



MIDI-based:
 HCodecs: Reads and writes MIDI files
 midi: Reads and writes MIDI files
 alsa-midi: Uses midi library
 YampaSynth: Stand-alone program


Haskore uses MIDI and other back-ends like Haskell

Re: [Haskell-cafe] Re: Haskell Propeganda

2008-08-24 Thread jeff p
Hello,

> Manual Typeable deriving should probably be disabled :-)
>
There are legitimate reasons to define your own Typeable instances.
Since Typeable already contains all the machinery you need to type a
standard functional language, it is nice to just add Typeable
instances when defining your own DSL which builds upon standard
language constructs; the alternative is to recreate the Typeable
machinery for your own type representations.

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


[Haskell-cafe] Re: Haskell Propeganda

2008-08-24 Thread Ashley Yakeley

Brandon S. Allbery KF8NH wrote:


typeOf / Typeable is itself an ugly special case,


Right.

> and really should be designed into the language

That's not necessary. The same thing can be done with top-level "<-" 
(see other thread).


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


Re: [Haskell-cafe] Re: Haskell Propeganda

2008-08-24 Thread Brandon S. Allbery KF8NH

On 2008 Aug 25, at 0:33, Ashley Yakeley wrote:

Don Stewart wrote:

You just wrote unsafeCoere# a different way:
   typeOf T = typeOf (undefined :: IORef ())


Right. It's straightforward to write unsafe segfaulting code in  
apparently safe Haskell.


typeOf / Typeable is itself an ugly special case, and really should be  
designed into the language:  it's about runtime type information.


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


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


[Haskell-cafe] Re: Haskell Propeganda

2008-08-24 Thread Ashley Yakeley

Don Stewart wrote:


You just wrote unsafeCoere# a different way:

typeOf T = typeOf (undefined :: IORef ())


Right. It's straightforward to write unsafe segfaulting code in 
apparently safe Haskell.



Manual Typeable deriving should probably be disabled :-)


Another ugly special-case hack. There's a better way.

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


Re: [Haskell-cafe] Re: Haskell Propeganda

2008-08-24 Thread Don Stewart
ashley:
> Thomas Davie wrote:
> >I'd be interested to see your other examples -- because that error is 
> >not happening in Haskell!  You can't argue that Haskell doesn't give you 
> >no segfaults, because you can embed a C segfault within Haskell.
> 
> This segfaults on my x86_64 Linux box:
> 
>   module Main where
>   import Data.Typeable
>   import Data.IORef
>   data T = T
>   instance Typeable T where
> typeOf _ = typeOf (undefined :: IORef ())
>   main :: IO ()
>   main = writeIORef (maybe undefined id (cast T)) ()
> 
> You'll note nothing marked "Foreign" or "unsafe", and only the base 
> library used. Does the segfault "happen in Haskell" or not?

You just wrote unsafeCoere# a different way:

typeOf T = typeOf (undefined :: IORef ())

Manual Typeable deriving should probably be disabled :-)

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


[Haskell-cafe] Re: Haskell Propeganda

2008-08-24 Thread Ashley Yakeley

Thomas Davie wrote:
I'd be interested to see your other examples -- because that error is 
not happening in Haskell!  You can't argue that Haskell doesn't give you 
no segfaults, because you can embed a C segfault within Haskell.


This segfaults on my x86_64 Linux box:

  module Main where
  import Data.Typeable
  import Data.IORef
  data T = T
  instance Typeable T where
typeOf _ = typeOf (undefined :: IORef ())
  main :: IO ()
  main = writeIORef (maybe undefined id (cast T)) ()

You'll note nothing marked "Foreign" or "unsafe", and only the base 
library used. Does the segfault "happen in Haskell" or not?


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


[Haskell-cafe] Re: [Haskell] Top Level <-

2008-08-24 Thread Ashley Yakeley

Duncan Coutts wrote:

This topic came up in #haskell this evening...

On Sun, 2008-08-24 at 16:12 -0700, Ashley Yakeley wrote:
1. Global mutable state. For instance, here's the count variable for 
Data.Unique rewritten:


   uniqSource :: MVar Integer
   uniqSource <- newMVarTL 0

Isn't that much nicer?



It's nicer syntax but it's still not true. There's still no such thing
as a global variable. There's always a scope.

In this case what scope are we looking for? Process scope? Only one
instance of uniqSource per process?


It is actually process scope, I believe. But it's one instance of 
"base-3.0.2.0:Data.Unique.uniqSource" per process: we don't care if 
there's also a "base-4.0:Data.Unique.uniqSource". The reason we don't 
care in this case is that base-3.0.2.0:Data.Unique.Unique and 
base-4.0:Data.Unique.Unique are different types, so they can't collide. 
These are different names in the same scope.


The scope I'm interested in is "Main.main" scope, i.e., the initialiser 
should be run no more than once per run of "main".


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


Re: [Haskell-cafe] Re: ANN: Mueval 0.5.1, 0.6, 0.6.1, 0.6.2, 0.6.3, 0.6.4

2008-08-24 Thread Gwern Branwen
On 2008.08.25 00:37:28 +0200, Ben Franksen <[EMAIL PROTECTED]> scribbled 0.4K 
characters:
> Gwern Branwen wrote:
> > All the stuff from the previous ANNs still apply here: you can get it at
> > ,
>
> Did that. Got:
>
> [EMAIL PROTECTED]: .../software/repos > mueval
> mueval: NotAllowed "Could not find module `Data.Number.BigFloat':\n  Use -v
> to see a list of the files searched for."
>
> (using ghc-6.8.3)
>
> Cheers
> Ben

Yes, mmorrow ran into this issue as well. Apparently a number of numeric 
modules just aren't installed for some people. I don't know why.

I fixed this in darcs Mueval by moving all the ones mmorrow identified as 
problematic into the allowable-but-not-defaults list. Seemed to work, although 
obviously if you/he specifically request --module Data.Number.BigFloat I would 
expect it to break again.

--
gwern
One SAO E.O.D. Propaganda LLNL Terrorism anarchy USSS forcast Chan


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


[Haskell-cafe] Re: [Haskell] Top Level <-

2008-08-24 Thread Duncan Coutts
This topic came up in #haskell this evening...

On Sun, 2008-08-24 at 16:12 -0700, Ashley Yakeley wrote:
> 1. Global mutable state. For instance, here's the count variable for 
> Data.Unique rewritten:
> 
>uniqSource :: MVar Integer
>uniqSource <- newMVarTL 0
> 
> Isn't that much nicer?
> 

It's nicer syntax but it's still not true. There's still no such thing
as a global variable. There's always a scope.

In this case what scope are we looking for? Process scope? Only one
instance of uniqSource per process? If so, it's not right. We can link
in multiple copies of a package and thereby end up with multiple
instances (this really happens, it's not a far fetched scenario).
So uniqSource is a package-name/version scope mutable variable.

To get the right thing for the annoying C libs that have 'global' init
and finalise functions you need something else. Not actually process
scope, that's too wide. You need exactly the same scope as the system
linker is using, so that we get one variable per instance of the C
library linked into the process. Consider a process using several dlls
where each one links to a C lib that needs 'global' initialisation, we
must have exactly one 'global' var instance per dll in this case because
that's the linker namespace scope.

The scope you need depends on the application. A language extension like
this is likely to only cover package-name/version scope, not scopes like
thread, OS thread, rts instance, linker, process, user account, OS,
subnet, interweb, planet etc.

So in practise, what scopes do we often need, and
does package-name/version scope correspond to many of those use cases?

Duncan

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


Re: [Haskell-cafe] Re: multi-core programming in Haskell

2008-08-24 Thread Don Stewart
ben.franksen:
> Galchin, Vasili wrote:
> > Thank you Murray. My post was not so clear  I was referring to
> > "automatic" parellelization vs "manual" parallelization. By "automatic" I
> > mean the programmer doesn't have to indicate where to parallelize ...
> > instead the compiler decides how to parallize!
> 
> Not on the horizon, it's too difficult. The best effort I know of
> automatically introduces par to the code /after running/ the program a few
> times (with the same given input data). There was some paper somewhere
> describing the idea and what the results were (IIRC, they achieved a
> respectable speedup in cases where there was enough potential for
> parallelization). Note this is /not/ something a compiler could do.

For restricted subsets of Haskell (e.g. data parallel array
programming), the compiler can essentially do this. But you have to
restrict yourself enough to make the problem (and cost model) tractably
to do automatically.

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


[Haskell-cafe] Re: multi-core programming in Haskell

2008-08-24 Thread Ben Franksen
Galchin, Vasili wrote:
> Thank you Murray. My post was not so clear  I was referring to
> "automatic" parellelization vs "manual" parallelization. By "automatic" I
> mean the programmer doesn't have to indicate where to parallelize ...
> instead the compiler decides how to parallize!

Not on the horizon, it's too difficult. The best effort I know of
automatically introduces par to the code /after running/ the program a few
times (with the same given input data). There was some paper somewhere
describing the idea and what the results were (IIRC, they achieved a
respectable speedup in cases where there was enough potential for
parallelization). Note this is /not/ something a compiler could do.

Cheers
Ben

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


[Haskell-cafe] Re: ANN: Mueval 0.5.1, 0.6, 0.6.1, 0.6.2, 0.6.3, 0.6.4

2008-08-24 Thread Ben Franksen
Gwern Branwen wrote:
> All the stuff from the previous ANNs still apply here: you can get it at
> , 

Did that. Got:

[EMAIL PROTECTED]: .../software/repos > mueval 
mueval: NotAllowed "Could not find module `Data.Number.BigFloat':\n  Use -v
to see a list of the files searched for."

(using ghc-6.8.3)

Cheers
Ben

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


[Haskell-cafe] Re: ANN: First Monad Tutorial of the Season

2008-08-24 Thread Ben Franksen
Hans van Thiel wrote:
> so 'The Greenhorn's Guide to becoming a Monad Cowboy' is on
> http://www.muitovar.com/monad/moncow.xhtml

Forgot to say: nicely written!

Some more comments:

You can declare a fixity (infixr) for flop instead of using parentheses
(yes, this is allowed; see 'elem' in the Prelude). Would make the code more
readable.

"(Recall that a type definition is just like a data definition, but with no
choice operator (|).)" First, you mean to say 'newtype', not 'type' (as in
the code). Second, a newtype may also contain only one data element (i.e.
one type expression after the constructor), not many, as in a data type
definition. Third, newtype is unlifted.

Cheers
Ben

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


[Haskell-cafe] Re: ANN: First Monad Tutorial of the Season

2008-08-24 Thread Ben Franksen
Hans van Thiel wrote:
> I'm proud to announce the first monad tutorial of the new season. It's
> under the Wiki permissive licence, but the web page has some clip art,
> so 'The Greenhorn's Guide to becoming a Monad Cowboy' is on
> http://www.muitovar.com/monad/moncow.xhtml

"First, let's talk about prefix, infix and postfix. Suppose you want to put
the argument of a unary function after the function (postfix)."

You mean 'before', not 'after'.

Cheers
Ben

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


Re: [Haskell-cafe] String to Double conversion in Haskell

2008-08-24 Thread Jefferson Heard
Because normally, Prelude.read covers this.  Don's link is the most
efficient, but you can also do

(read . ByteString.unpack $ bytestring) :: Double

to get a Double from a printed representation of most numbers.

2008/8/24 Daryoush Mehrtash <[EMAIL PROTECTED]>:
> I am curious to understand the logic, the "Haskell Think", here.  Why is it
> that the byteString only supports conversion to int.
>
> daryoush
> On Sun, Aug 24, 2008 at 2:23 PM, Don Stewart <[EMAIL PROTECTED]> wrote:
>>
>> dmehrtash:
>> >I am trying to convert a string to a float.  It seems that
>> > Data.ByteString
>> >library only supports readInt.After some googling I came accross
>> > a
>> >possibloe implementation: [1]http://sequence.svcs.cs.pdx.edu/node/373
>> >
>>
>> Use the bytstring-lexing library,
>>
>>
>>  http://hackage.haskell.org/cgi-bin/hackage-scripts/package/bytestring-lexing
>>
>> Which provides a copying and non-copying lexer for doubles,
>>
>>readDouble   :: ByteString -> Maybe (Double, ByteString)
>>unsafeReadDouble :: ByteString -> Maybe (Double, ByteString)
>>
>> -- Don
>
>
>
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>



-- 
I try to take things like a crow; war and chaos don't always ruin a
picnic, they just mean you have to be careful what you swallow.

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


Re: [Haskell-cafe] String to Double conversion in Haskell

2008-08-24 Thread Don Stewart
We wrote a readInt a long time ago, because we needed it. It turns out
that really though, there's a large class of functions for parsing
bytestrings should come with, so I've started adding those to the
bytestring-lexing package.

In hindisight ByteString.readInt should have been in a separate package.

-- Don


dmehrtash:
>I am curious to understand the logic, the "Haskell Think", here.  Why is
>it that the byteString only supports conversion to int.
> 
>daryoush
>On Sun, Aug 24, 2008 at 2:23 PM, Don Stewart <[EMAIL PROTECTED]> wrote:
> 
>  dmehrtash:
>  >I am trying to convert a string to a float.  It seems that
>  Data.ByteString
>  >library only supports readInt.After some googling I came
>  accross a
>  >possibloe implementation:
>  [1][2]http://sequence.svcs.cs.pdx.edu/node/373
>  >
> 
>  Use the bytstring-lexing library,
> 
>   
>   
> [3]http://hackage.haskell.org/cgi-bin/hackage-scripts/package/bytestring-lexing
> 
>  Which provides a copying and non-copying lexer for doubles,
> 
> readDouble   :: ByteString -> Maybe (Double, ByteString)
> unsafeReadDouble :: ByteString -> Maybe (Double, ByteString)
>  -- Don
> 
> References
> 
>Visible links
>1. mailto:[EMAIL PROTECTED]
>2. http://sequence.svcs.cs.pdx.edu/node/373
>3. 
> http://hackage.haskell.org/cgi-bin/hackage-scripts/package/bytestring-lexing
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] String to Double conversion in Haskell

2008-08-24 Thread Daryoush Mehrtash
I am curious to understand the logic, the "Haskell Think", here.  Why is it
that the byteString only supports conversion to int.

daryoush
On Sun, Aug 24, 2008 at 2:23 PM, Don Stewart <[EMAIL PROTECTED]> wrote:

> dmehrtash:
> >I am trying to convert a string to a float.  It seems that
> Data.ByteString
> >library only supports readInt.After some googling I came accross a
> >possibloe implementation: [1]http://sequence.svcs.cs.pdx.edu/node/373
> >
>
> Use the bytstring-lexing library,
>
>
> http://hackage.haskell.org/cgi-bin/hackage-scripts/package/bytestring-lexing
>
> Which provides a copying and non-copying lexer for doubles,
>
>readDouble   :: ByteString -> Maybe (Double, ByteString)
>unsafeReadDouble :: ByteString -> Maybe (Double, ByteString)
>
> -- Don
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] String to Double conversion in Haskell

2008-08-24 Thread Thomas Davie


On 24 Aug 2008, at 23:23, Don Stewart wrote:


dmehrtash:
  I am trying to convert a string to a float.  It seems that  
Data.ByteString
  library only supports readInt.After some googling I came  
accross a

  possibloe implementation: [1]http://sequence.svcs.cs.pdx.edu/node/373



Use the bytstring-lexing library,

   http://hackage.haskell.org/cgi-bin/hackage-scripts/package/bytestring-lexing

Which provides a copying and non-copying lexer for doubles,

   readDouble   :: ByteString -> Maybe (Double, ByteString)
   unsafeReadDouble :: ByteString -> Maybe (Double, ByteString)


Incidentally, is there any reason we can't have this for Lazy BSes?

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


Re: [Haskell-cafe] String to Double conversion in Haskell

2008-08-24 Thread Don Stewart
dmehrtash:
>I am trying to convert a string to a float.  It seems that Data.ByteString
>library only supports readInt.After some googling I came accross a
>possibloe implementation: [1]http://sequence.svcs.cs.pdx.edu/node/373
> 

Use the bytstring-lexing library,

http://hackage.haskell.org/cgi-bin/hackage-scripts/package/bytestring-lexing

Which provides a copying and non-copying lexer for doubles,

readDouble   :: ByteString -> Maybe (Double, ByteString)
unsafeReadDouble :: ByteString -> Maybe (Double, ByteString)

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


[Haskell-cafe] String to Double conversion in Haskell

2008-08-24 Thread Daryoush Mehrtash
I am trying to convert a string to a float.  It seems that Data.ByteString
library only supports readInt.After some googling I came accross a
possibloe implementation: http://sequence.svcs.cs.pdx.edu/node/373

My questions are:

a) is there a standard library implementation of string -> Double and float?
b) Why is it that the ByteString only supports readInt? Is there a reason
for it?


Thanks,

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


Re: [Haskell-cafe] Haskell audio libraries & audio formats

2008-08-24 Thread Eric Kidd
On Sun, Aug 24, 2008 at 4:13 PM, John Van Enk <[EMAIL PROTECTED]> wrote:
> I'm guessing that some sort of unboxed array would be close to what I want.
> If you have suggestions, I'm more than open to them. (This is my first
> attempt at writing a library.)

I'm still trying to answer this question myself. :-) I'll let you know
how HCodec's AudioData format actually works in practice once I my
code is converted.

Honestly, an ideal format should allow iteration over one or more
StorableArray chunks. This would make it much easier to interact with
the outside world. Unfortunately, HCodec's DiffUArray format seems to
require a conversion step to get a StorableArray, so I'm going to have
to benchmark it.

Good luck with your first Haskell library!

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


Re: [Haskell-cafe] Haskell audio libraries & audio formats

2008-08-24 Thread John Van Enk
Eric,

I was hoping to use a packed format like ByteString eventually. Right now, I
want to get everything working nicely. As it stands, I end up marshaling a
lot of information into/out of arrays which I'd much rather keep as a block
of memory.

I'm guessing that some sort of unboxed array would be close to what I want.
If you have suggestions, I'm more than open to them. (This is my first
attempt at writing a library.)

/jve

On Sun, Aug 24, 2008 at 1:06 PM, Eric Kidd <[EMAIL PROTECTED]> wrote:

> On Sun, Aug 24, 2008 at 12:41 PM, John Van Enk <[EMAIL PROTECTED]> wrote:
> > It implements the Haskell bindings to the PortAudio library. This is the
> > library behind Audacious. I *have not* implemented the callback model
> yet,
> > but I plan to do that.
> >
> > Perhaps this will be something which is useful to you?
>
> Looks like a great binding! We actually use portaudio in callback mode
> at work, with reasonable success (from C++).
>
> One question: I notice that your writeStream function represents audio
> using '[[a]]'.
>
>  writeStream :: (Storable a) => PaStream a -- ^ The output stream
>  -> [[a]]-- ^ The samples to be played
>  -> Int  -- ^ Number of frames
>  -> IO (Either String ErrorCode) -- ^ The return status
> of the write
>
> In my experiments, I've been somewhat unsatisfied with the performance
> of '[[a]]' as an audio format. Would you be interested in also
> supporting an array-based format for audio data?
>
> I'm currently converting my program to use HCodec's Data.Audio
> representation, which looks pretty promising. I don't know how it
> performs yet, but I'll let you know.
>
> Thank you for the pointer to your library! It will make an excellent
> addition to the available Haskell sound libraries.
>
> Cheers,
> Eric
>



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


Re: [Haskell-cafe] Haskell audio libraries & audio formats

2008-08-24 Thread Don Stewart
haskell:
> At the end of this e-mail, you can find a list of Haskell sound
> libraries and their supported audio formats.

Could you add that detail to the Haskell wiki Audio page?

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


Re: [Haskell-cafe] Why doesn't this work?

2008-08-24 Thread Yitzchak Gale
I wrote:
>> A more basic issue is that fn is in the IO monad,
>> but its use inside the mapM will need it to be in the ST
>> monad.

Daniel Fischer wrote:
> No,
> return (fn particle) :: ST s (IO ())
> , so that's fine.

Ah, true. But I doubt that Andrew really meant to
do the calculation in ST s (IO ()).

> Indeed, filling in a few dummies, the code compiles
> with the 6.8 branch.

So then the only way to know why it didn't compile
for Andrew is if we see more of the code.

But that's only a technical issue. I hope that now
Andrew has a better idea about what's wrong.
If not - please let us know.

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


Re: [Haskell-cafe] Haskell audio libraries & audio formats

2008-08-24 Thread Eric Kidd
On Sun, Aug 24, 2008 at 12:41 PM, John Van Enk <[EMAIL PROTECTED]> wrote:
> It implements the Haskell bindings to the PortAudio library. This is the
> library behind Audacious. I *have not* implemented the callback model yet,
> but I plan to do that.
>
> Perhaps this will be something which is useful to you?

Looks like a great binding! We actually use portaudio in callback mode
at work, with reasonable success (from C++).

One question: I notice that your writeStream function represents audio
using '[[a]]'.

  writeStream :: (Storable a) => PaStream a -- ^ The output stream
  -> [[a]]-- ^ The samples to be played
  -> Int  -- ^ Number of frames
  -> IO (Either String ErrorCode) -- ^ The return status
of the write

In my experiments, I've been somewhat unsatisfied with the performance
of '[[a]]' as an audio format. Would you be interested in also
supporting an array-based format for audio data?

I'm currently converting my program to use HCodec's Data.Audio
representation, which looks pretty promising. I don't know how it
performs yet, but I'll let you know.

Thank you for the pointer to your library! It will make an excellent
addition to the available Haskell sound libraries.

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


Re: [Haskell-cafe] Haskell audio libraries & audio formats

2008-08-24 Thread John Van Enk
Eric,

I'm hoping to publish my library in the next week here:

darcs get http://code.haskell.org/portaudio/

It implements the Haskell bindings to the PortAudio library. This is the
library behind Audacious. I *have not* implemented the callback model yet,
but I plan to do that.

Perhaps this will be something which is useful to you?

On Sun, Aug 24, 2008 at 11:41 AM, Eric Kidd <[EMAIL PROTECTED]> wrote:

> Greetings, Haskell folks!
>
> I'm working on a toy program for drum synthesis.  This has lead me to
> explore the various sound-related libraries in Hackage.  Along the way,
> I've learned several things:
>
>  1. There's a lot of Haskell sound libraries, but no agreement on how
> to represent buffers of audio data.
>  2. Some of the most useful sound libraries aren't listed in Hackage's
> "Sound" section, including HCodecs, SDL-mixer and hogg.
>  3. The Haskell OpenAL bindings are great, but ALUT has been removed
> from MacOS 10.5.  Of course, a pure-Haskell version of ALUT would
> be pretty easy to write, and it could be used as a fallback.
>  4. '[[a]]' is _not_ a good representation for multi-channel audio
> data.  Manipulating even 10 seconds of audio is noticeably slow.
>  5. HCodecs is probably the best library for reading WAVE files.  It
> uses 'DiffUArray Int a' to represent audio data, and not '[[a]]'.
> It also supports MIDI and SoundFont, which is quite handy.
>  6. YampaSynth looks really cool, and it might be possible to turn it
> into a reusable MIDI synthesizer library for use with HCodecs.
> This would be extremely useful: it would provide a basis for all
> kinds of crazy MIDI-based programming in Haskell.
>
> At the end of this e-mail, you can find a list of Haskell sound
> libraries and their supported audio formats.
>
> What would the ideal Haskell sound API look like?  Personally, I would
> love to see:
>
>  a. Something like HCodecs's Data.Audio as the basic sound format.
> Data.Audio is an array-based API, and it supports converting
> between a wide range of common sample formats.  I don't know how
> fast this is, but it already exists, and it's used by YampaSynth.
>  b. OpenAL for sound playback, with a portable version of ALUT.  This
> may require writing a pure-Haskell version of ALUT.
>  c. Utility functions to convert Data.Audio to OpenAL.AL.Buffer.
>  d. An easy-to-use API for audio processing.  It might be possible to
> start with something like Jack's 'mainMono' and 'mainStereo'
> functions, which map a function over an audio stream.
>
> Other nice-to-have features might include:
>
>  e. A standard MIDI format, based on either the HCodecs package or the
> midi package.  (HCodecs is used by YampaSynth, and the midi package
> is used by alsa-midi.)
>  f. A modular version of YampaSynth which can convert MIDI data
> structures into Data.Audio values.
>
> It looks like Haskell could be a really sweet audio programming
> environment with just a bit of integration work.  What do folks think?
> Are there other libraries I should look at more closely?  Other features
> that should be included in an ideal audio API?
>
> Thank you for your advice and feedback!
>
> Cheers,
> Eric
>
>
> Haskell audio libraries
>
> Reading and writing sound files:
>  HCodecs: (Audible a) => DiffUArray Int a
>  hsndfile: MArray with Float and Double
>  HSoundFile: [[Double]]
>  ALUT: OpenAL.AL.Buffer
>  WAVE: [[Int32]]
>
> Playing sounds:
>  OpenAL: Ptr UInt8, Ptr Int16, 1-N channels
>  SDL-mixer: ForeignPtr ChunkStruct, ForeignPtr MusicStruct
>
> Sound processing libraries:
>  dsp: Array a, [a]
>  jack: Operates via mapping functions
>mainMono :: (CFloat -> IO CFloat) -> IO ()
>mainStereo :: ((CFloat, CFloat) -> IO (CFloat, CFloat)) -> IO ()
>
> MIDI-based:
>  HCodecs: Reads and writes MIDI files
>  midi: Reads and writes MIDI files
>  alsa-midi: Uses midi library
>  YampaSynth: Stand-alone program
>
> Special-purpose APIs only (FFIs, etc.):
>  hCsound: CsoundPtr
>  hsc3: UGen
>
> No public sound-buffer API:
>  hbeat: The relevant source files are missing!
>  hogg: Very low-level API for Ogg internals only
>  libmpd: No sound buffer API
>  sonic-visualizer: No sound buffer API
>  truelevel: Stand-alone program (uses WAVE)
>  wavconvert: Stand-alone program
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>



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


Re: [Haskell-cafe] Why doesn't this work?

2008-08-24 Thread Emil Axelsson

BTW, this is a case where it may be more convenient to use forM:

 forM ps $ \pix -> do
   particle <- read_grid g pix
   return $ fn particle

(untested...)

forM is just another way of saying (flip mapM).

/ Emil



Andrew Coppin skrev:

colour_grid :: (Particle -> IO ()) -> Grid ph -> IO ()
colour_grid fn g = sequence_ $ runST $ do
 ps <- grid_coords g

 mapM
   (\pix -> do
 particle <- read_grid g pix
 return $ fn particle
   )
   ps

When I attempt to run this, GHCi just gives me a very cryptic type 
checker error. I can't figure out what's wrong here. As far as I can 
tell, this should run...


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

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


Re: [Haskell-cafe] Haskell Propeganda

2008-08-24 Thread Brandon S. Allbery KF8NH

On 2008 Aug 24, at 7:16, C.M.Brown wrote:

OK, so you're basically saying that segfaults can be eliminated with a
strong type system, whereas pattern matching errors is the result of  
some


Not really, no.  A sufficiently strong type system will eliminate  
segfaults (modulo bugs in the language runtime or erroneous use of the  
FFI); but Haskell arguably doesn't have a sufficiently strong type  
system:  pattern match errors being the symptom, and the resolution is  
dependent types.


That said, what I was really saying was that a pattern match error  
still gives you more information, and more easily, than a segfault:   
if it's not something trivial like dereferencing a null pointer, the  
segfault may well be in completely unrelated code because the  
erroneous operation (for example) overran a buffer and corrupted  
unrelated data.  Whereas with laziness, you may have to do some  
footwork to find the actual error (ghci's debugger helps, as does hpc  
as someone else mentioned upthread) but it's deterministic.


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


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


Re: [Haskell-cafe] Haskell Propeganda

2008-08-24 Thread Brandon S. Allbery KF8NH

On 2008 Aug 24, at 4:00, Thomas Davie wrote:

On 24 Aug 2008, at 05:04, Albert Y. C. Lai wrote:

"Dear friends, Haskell prevents more errors and earlier." This is  
honest, relevant, good advocacy.


"Dear friends, segfaults are type errors, not logical errors." Why  
would you indulge in this? It's even less relevant than bikeshed  
colours.


Is it?  when I write C I spend a lot of my time sat in gdb trying to  
figure out where the error that the Haskell type system would have  
caught for me is.  This is *very* relevant, it's right at the bottom  
line of whether I'm more productive in Haskell or in C.



Half agreed.  It occurs to me this morning that one thing to consider  
is that often segfaults are more the kind of error that requires  
dependent types, which are Hard in Haskell (see, for example, the  
discussion of type-level naturals elsethread).  (Example:  copying a  
buffer when the copy length is negative due to a bug.)


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


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


[Haskell-cafe] Haskell audio libraries & audio formats

2008-08-24 Thread Eric Kidd
Greetings, Haskell folks!

I'm working on a toy program for drum synthesis.  This has lead me to
explore the various sound-related libraries in Hackage.  Along the way,
I've learned several things:

  1. There's a lot of Haskell sound libraries, but no agreement on how
 to represent buffers of audio data.
  2. Some of the most useful sound libraries aren't listed in Hackage's
 "Sound" section, including HCodecs, SDL-mixer and hogg.
  3. The Haskell OpenAL bindings are great, but ALUT has been removed
 from MacOS 10.5.  Of course, a pure-Haskell version of ALUT would
 be pretty easy to write, and it could be used as a fallback.
  4. '[[a]]' is _not_ a good representation for multi-channel audio
 data.  Manipulating even 10 seconds of audio is noticeably slow.
  5. HCodecs is probably the best library for reading WAVE files.  It
 uses 'DiffUArray Int a' to represent audio data, and not '[[a]]'.
 It also supports MIDI and SoundFont, which is quite handy.
  6. YampaSynth looks really cool, and it might be possible to turn it
 into a reusable MIDI synthesizer library for use with HCodecs.
 This would be extremely useful: it would provide a basis for all
 kinds of crazy MIDI-based programming in Haskell.

At the end of this e-mail, you can find a list of Haskell sound
libraries and their supported audio formats.

What would the ideal Haskell sound API look like?  Personally, I would
love to see:

  a. Something like HCodecs's Data.Audio as the basic sound format.
 Data.Audio is an array-based API, and it supports converting
 between a wide range of common sample formats.  I don't know how
 fast this is, but it already exists, and it's used by YampaSynth.
  b. OpenAL for sound playback, with a portable version of ALUT.  This
 may require writing a pure-Haskell version of ALUT.
  c. Utility functions to convert Data.Audio to OpenAL.AL.Buffer.
  d. An easy-to-use API for audio processing.  It might be possible to
 start with something like Jack's 'mainMono' and 'mainStereo'
 functions, which map a function over an audio stream.

Other nice-to-have features might include:

  e. A standard MIDI format, based on either the HCodecs package or the
 midi package.  (HCodecs is used by YampaSynth, and the midi package
 is used by alsa-midi.)
  f. A modular version of YampaSynth which can convert MIDI data
 structures into Data.Audio values.

It looks like Haskell could be a really sweet audio programming
environment with just a bit of integration work.  What do folks think?
Are there other libraries I should look at more closely?  Other features
that should be included in an ideal audio API?

Thank you for your advice and feedback!

Cheers,
Eric


Haskell audio libraries

Reading and writing sound files:
  HCodecs: (Audible a) => DiffUArray Int a
  hsndfile: MArray with Float and Double
  HSoundFile: [[Double]]
  ALUT: OpenAL.AL.Buffer
  WAVE: [[Int32]]

Playing sounds:
  OpenAL: Ptr UInt8, Ptr Int16, 1-N channels
  SDL-mixer: ForeignPtr ChunkStruct, ForeignPtr MusicStruct

Sound processing libraries:
  dsp: Array a, [a]
  jack: Operates via mapping functions
mainMono :: (CFloat -> IO CFloat) -> IO ()
mainStereo :: ((CFloat, CFloat) -> IO (CFloat, CFloat)) -> IO ()

MIDI-based:
  HCodecs: Reads and writes MIDI files
  midi: Reads and writes MIDI files
  alsa-midi: Uses midi library
  YampaSynth: Stand-alone program

Special-purpose APIs only (FFIs, etc.):
  hCsound: CsoundPtr
  hsc3: UGen

No public sound-buffer API:
  hbeat: The relevant source files are missing!
  hogg: Very low-level API for Ogg internals only
  libmpd: No sound buffer API
  sonic-visualizer: No sound buffer API
  truelevel: Stand-alone program (uses WAVE)
  wavconvert: Stand-alone program
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why doesn't this work?

2008-08-24 Thread Daniel Fischer
Am Sonntag, 24. August 2008 17:21 schrieb Yitzchak Gale:
> Alfonso Acosta wrote:
> > I haven't tried to run the code, but my first bet is that, due to the
> > rank-2 polymorphism of ST, you should use parenthesis instead of $ in
> > the case of runST.
>
> Perhaps if Andrew is using an old compiler.
> That is no longer a problem in recent versions of GHC.
>
> A more basic issue is that fn is in the IO monad,
> but its use inside the mapM will need it to be in the ST
> monad.

No,
return (fn particle) :: ST s (IO ())
, so that's fine.

Indeed, filling in a few dummies, the code compiles with the 6.8 branch.

>
> Regards,
> Yitz

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


Re: [Haskell-cafe] Why doesn't this work?

2008-08-24 Thread Yitzchak Gale
Alfonso Acosta wrote:
> I haven't tried to run the code, but my first bet is that, due to the
> rank-2 polymorphism of ST, you should use parenthesis instead of $ in
> the case of runST.

Perhaps if Andrew is using an old compiler.
That is no longer a problem in recent versions of GHC.

A more basic issue is that fn is in the IO monad,
but its use inside the mapM will need it to be in the ST
monad.

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


Re: [Haskell-cafe] Haskell Propeganda

2008-08-24 Thread Thomas M. DuBuisson
Chris said:
> I personally think such pattern matching errors
> are a weaknesss of the language; with possibly no solutions to resolve.

Actually tools like CATCH [1] exist and could be incorporated into a
compiler to eliminate this problem.

[1] http://www-users.cs.york.ac.uk/~ndm/catch/

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


Re: [Haskell-cafe] Haskell Speed Myth

2008-08-24 Thread Thomas M. DuBuisson
> Hmm thanks, that's interesting -- I was think it was probably caused  
> by OS X, but it appears to happen on Linux too.  Could you try running  
> the old code too, and see if you experience the order of magnitude  
> slowdown too?

The original program on my Linux 2.6.26 Core2 Duo:

[EMAIL PROTECTED] Test]$ time ./tr-threaded 100
37

real0m0.635s
user0m0.530s
sys 0m0.077s
[EMAIL PROTECTED] Test]$ time ./tr-nothreaded 100
37

real0m0.352s
user0m0.350s
sys 0m0.000s
[EMAIL PROTECTED] Test]$ time ./tr-threaded 100 +RTS -N2
37

real0m13.954s
user0m4.333s
sys 0m5.736s

--

Seeing as there still was obviously not enough computation to justify
the OS threads in my last example, I made a test where it hashed a 32
byte string (show . md5 . encode $ val):
[EMAIL PROTECTED] Test]$ time ./threadring-nothreaded 100
50
552

real0m1.408s
user0m1.323s
sys 0m0.083s
[EMAIL PROTECTED] Test]$ time ./threadring-threaded 100
50
552

real0m1.948s
user0m1.807s
sys 0m0.143s
[EMAIL PROTECTED] Test]$ time ./threadring-threaded 100 +RTS -N2
552
50

real0m1.663s
user0m1.427s
sys 0m0.237s
[EMAIL PROTECTED] Test]$ 

---

Seeing as this still doesn't beat the old RTS, I decided to increase the
per unit work a little more.  This code will hash 10KB every time the
token is passed / decremented.

[EMAIL PROTECTED] Test]$ time ./threadring-nothreaded 10
(308,77851ef5e9e781c04850a7df9cc855d2)


real2m56.453s
user2m55.399s
sys 0m0.457s

[EMAIL PROTECTED] Test]$ time ./threadring-threaded 10 
(308,77851ef5e9e781c04850a7df9cc855d2)


real3m6.430s
user3m5.868s
sys 0m0.460s

[EMAIL PROTECTED] Test]$ time ./threadring-threaded 10 +RTS -N2
(810,77851ef5e9e781c04850a7df9cc855d2)
(308,77851ef5e9e781c04850a7df9cc855d2)


real1m55.616s
user2m47.982s
sys 0m3.586s

* Yes, I notice its exiting before the output gets printed a couple
times, oh well.

-
REFLECTION

Yay, the multicore version pays off when the workload is non-trivial.
CPU utilization is still rather low for the -N2 case (70%).  I think the
Haskell threads have an affinity for certain OS threads (and thus a
CPU).  Perhaps it results in a CPU having both tokens of work and the
other having none?  

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


[Haskell-cafe] (no subject)

2008-08-24 Thread john lask

Hi

has anyone had any success in running a recent version of hs-plugins on a 
windows platform. I refer to this post to the haskell list in December last 
year. The current version of hs-plugins dosn't appear to work either. Same 
problem ...


http://www.haskell.org/pipermail/haskell/2007-December/020043.html


jvl

_
Meet singles near you. Try ninemsn dating now!
http://a.ninemsn.com.au/b.aspx?URL=http%3A%2F%2Fdating%2Eninemsn%2Ecom%2Eau%2Fchannel%2Findex%2Easpx%3Ftrackingid%3D1046247&_t=773166080&_r=WL_TAGLINE&_m=EXT___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why doesn't this work?

2008-08-24 Thread Alfonso Acosta
I haven't tried to run the code, but my first bet is that, due to the
rank-2 polymorphism of ST, you should use parenthesis instead of $ in
the case of runST.

On Sun, Aug 24, 2008 at 3:25 PM, Andrew Coppin
<[EMAIL PROTECTED]> wrote:
> colour_grid :: (Particle -> IO ()) -> Grid ph -> IO ()
> colour_grid fn g = sequence_ $ runST $ do
>  ps <- grid_coords g
>
>  mapM
>   (\pix -> do
> particle <- read_grid g pix
> return $ fn particle
>   )
>   ps
>
> When I attempt to run this, GHCi just gives me a very cryptic type checker
> error. I can't figure out what's wrong here. As far as I can tell, this
> should run...
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Why doesn't this work?

2008-08-24 Thread Andrew Coppin

colour_grid :: (Particle -> IO ()) -> Grid ph -> IO ()
colour_grid fn g = sequence_ $ runST $ do
 ps <- grid_coords g

 mapM
   (\pix -> do
 particle <- read_grid g pix
 return $ fn particle
   )
   ps

When I attempt to run this, GHCi just gives me a very cryptic type 
checker error. I can't figure out what's wrong here. As far as I can 
tell, this should run...


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


Re: [Haskell-cafe] Haskell Propeganda

2008-08-24 Thread C.M.Brown
Hi Brandon,

OK, so you're basically saying that segfaults can be eliminated with a
strong type system, whereas pattern matching errors is the result of some
dodgy laziness going on? I personally think such pattern matching errors
are a weaknesss of the language; with possibly no solutions to resolve.

regards,
Chris.



On Sat, 23 Aug 2008, Brandon S. Allbery KF8NH wrote:

> On 2008 Aug 23, at 17:29, C.M.Brown wrote:
> > I wonder whether seg faults are the true analogue to errors such as
> > "error: head empty list." or pattern match errors.
>
> Not really; while laziness does introduce a certain amount of "spooky
> action at a difference" to such errors, it's not nearly as bad as the
> memory corruption (due to effective type mismatches) that often leads
> to the segfault.
>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type family fun

2008-08-24 Thread Ryan Ingram
On Sun, Aug 24, 2008 at 1:44 AM, Stefan Holdermans <[EMAIL PROTECTED]> wrote:
] Your calls to empty are just ambiguous.

Now, you are probably wondering how to fix it.  Here's two different solutions:

> {-# LANGUAGE TypeFamilies, TypeOperators, ScopedTypeVariables #-}
> module Ix where

The first solution still uses type families, but "empty" takes a
parameter so that the which instance to use can be chosen
unambiguously.

> class Ix i where
> type IxMap i :: * -> *
> empty :: i -> IxMap i [Int]

> -- uses ScopedTypeVariables
> instance (Ix left, Ix right) => Ix (left :|: right) where
>type IxMap (left :|: right) = BiApp (IxMap left) (IxMap right)
>empty _ = BiApp (empty (undefined :: left)) (empty (undefined :: right))

The second solution uses data families instead, because no such
ambiguity can exist.

> class IxD i where
> data IxMapD i :: * -> *
> emptyD :: IxMapD i [Int]

> instance (IxD left, IxD right) => IxD (left :|: right) where
> data IxMapD (left :|: right) a = BiAppD (IxMapD left a) (IxMapD right a)
> emptyD = BiAppD emptyD emptyD

  -- ryan

> data (:|:) a b = Inl a | Inr b
> data BiApp a b c = BiApp (a c) (b c)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type family fun

2008-08-24 Thread Stefan Holdermans

Chris,

In the inferred type, there should be IxMap l instead of IxMap i,  
does anybody know what I'm doing wrong?


Your calls to empty are just ambiguous.

Let's say I want to get a hold of an empty map for A :|: B for some  
types A and B. And let's say that you've instance for A hanging around  
that specifies type IxMap A = C. Now our call to empty for A :|: B  
delegates to empty to get the left map. Clearly you expect it to call  
to the instance for A, but any type D with IxMap D = C would do.


Does that make sense?

Cheers,

  Stefan

On Aug 23, 2008, at 4:55 PM, Chris Eidhof wrote:


Hey all,

I was playing around with type families, and I have a strange problem.

Suppose we have an alternative to an Either datatype:

> data (:|:) a b = Inl a | Inr b

and a class Ix:

> class Ix i where
>   type IxMap i :: * -> *
>   empty  :: IxMap i [Int]

Now I want to give an instance for (a :|: b):

> instance (Ix l, Ix r) => Ix (l :|: r) where
>   type IxMap (l :|: r) = BiApp (IxMap l) (IxMap r)
>   empty = BiApp empty empty

BiApp is defined as following:

> data BiApp a b c = BiApp (a c) (b c)

However, it looks like the recursive calls to empty can't be  
unified, I get the following error message:


   Couldn't match expected type `IxMap l'
  against inferred type `IxMap i'
 Expected type: IxMap (l :|: r) [Int]
 Inferred type: BiApp (IxMap i) (IxMap i1) [Int]
   In the expression: BiApp empty empty
   In the definition of `empty': empty = BiApp empty empty

In the inferred type, there should be IxMap l instead of IxMap i,  
does anybody know what I'm doing wrong?


Thanks,

-chris

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


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


Re: [Haskell-cafe] Haskell Speed Myth

2008-08-24 Thread Thomas Davie


On 24 Aug 2008, at 06:31, Thomas M. DuBuisson wrote:




That's really interesting -- I just tried this.

Compiling not using -threaded: 1.289 seconds
Compiling using -threaded, but not running with -N2: 3.403 seconds
Compiling using -threaded, and using -N2: 55.072 seconds



I was hoping to see a relative improvement when introducting an
opportunity parallelism in the program, so I made a version with two
MVars filled at the start.  This didn't work out though - perhaps some
performance stands to be gained by improving the GHC scheduler wrt  
cpu /

OS thread affinity for the Haskell threads?

For the curious:

-O2: 7.3 seconds (CPU: 99.7% user)
-O2 -threaded: 11.5 seconds (CPU: 95% user, 5% system)
-O2 -threaded ... +RTS -N2: killed after 3 minutes (CPUs: 15% user,  
20%

system)

Thats quite a lot of CPU time going to the system.

Specs:
Linux 2.6.26 (Arch) x86_64
Intel Core 2 Duo 2.5GHz


Hmm thanks, that's interesting -- I was think it was probably caused  
by OS X, but it appears to happen on Linux too.  Could you try running  
the old code too, and see if you experience the order of magnitude  
slowdown too?


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


Re: [Haskell-cafe] ANN: benchpress 0.2.1

2008-08-24 Thread Johan Tibell
On Tue, Aug 19, 2008 at 9:37 AM, Bas van Dijk <[EMAIL PROTECTED]> wrote:
> On Tue, Aug 19, 2008 at 8:49 AM, Johan Tibell <[EMAIL PROTECTED]> wrote:
>> benchpress is a micro-benchmark library that produces statistics such
>> as min, mean, standard deviation, median, and max execution time. It
>> also computes execution time percentiles.
>
> Nice, I'm certainty going to use this. Thanks!
>
> It would be even nicer if you could also measure the elapsed CPU time
> (using System.CPUTime.getCPUTime). Than the measurement is not
> influenced by time spent in other processes and IO time.

Available in 0.2.2 on Hackage.

Cheers,

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


Re: [Haskell-cafe] Haskell Speed Myth

2008-08-24 Thread Thomas Davie


On 24 Aug 2008, at 01:26, Brandon S. Allbery KF8NH wrote:


On 2008 Aug 23, at 18:34, Krzysztof Skrzętnicki wrote:

Recently I wrote computation intensive program that could easily
utilize both cores. However, there was overhead just from compiling
with -threaded and making some forkIO's. Still, the overhead was not
larger than 50% and with 4 cores I would probably still get the
results faster - I didn't experience an order of magnitude slowdown.
Perhaps it's the issue with OS X.



All that's needed for multicore to be a *lot* slower is doing it  
wrong.  Make sure you're forcing the right things in the right  
places, or you could quietly be building up thunks on both cores  
that will cause lots of cross-core signaling or locking.  And, well,  
make sure the generated code isn't stupid.  Quite possibly the PPC  
code is an order of magnitude worse than the better-tested Intel code.


Except that the test was running on a Core2Duo, and it runs very fast  
when ghc does the threading on one core.  My personal guess is that to  
do it properly threaded requires *lots* of kernel boundary crosses to  
do the locking etc on OS X (being a nearly-micro-kernel).  The test  
program was almost 100% made up of thread locking code.


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


Re: [Haskell-cafe] Reader monad, implicit parameters, or something else altogether?

2008-08-24 Thread Henning Thielemann


On Fri, 22 Aug 2008, Alexander Dunlap wrote:


You can always change how you unsafePerformIO the data, though. If you
want to set Planck's constant to 42 (or whatever), just change the
unsafePerformIO $  to unsafePerformIO $ return 42.


you can't change it at runtime

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


Re: [Haskell-cafe] Haskell Propeganda

2008-08-24 Thread Thomas Davie


On 24 Aug 2008, at 05:04, Albert Y. C. Lai wrote:

"Dear friends, Haskell prevents more errors and earlier." This is  
honest, relevant, good advocacy.


"Dear friends, segfaults are type errors, not logical errors." Why  
would you indulge in this? It's even less relevant than bikeshed  
colours.


Is it?  when I write C I spend a lot of my time sat in gdb trying to  
figure out where the error that the Haskell type system would have  
caught for me is.  This is *very* relevant, it's right at the bottom  
line of whether I'm more productive in Haskell or in C.


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


Re: [Haskell-cafe] Lines of code metrics

2008-08-24 Thread Henning Thielemann


On Thu, 21 Aug 2008, Johannes Waldmann wrote:


NB: My private set of Haskell metrics:
* lines of code (per declaration) (should be <= 5)
* number of declarations (per module) (should be <= 5 as well :-)
* number of usages of Int, String, List, IO (should be <= 0 :-) :-)


* number of usages of unsafePerformIO, unsafeInterleaveIO, use of Ptr or 
IO at all



These would be nice metrics for me to decide, whether I want to download a 
package from Hackage.

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