[Haskell-cafe] How to fix linker errors when creating a package using cabal

2007-08-25 Thread Peter Verswyvelen
I'm trying to make a package of Ben.Lippmeier's very nice ANUPlot graphics
library (http://cs.anu.edu.au/people/Ben.Lippmeier)

IMHO this would be a great contribution to the Haskell library, it's very
clean code for newbies :)

I created the following cabal file:

name: Plot
version: 1.1
license: AllRightsReserved
maintainer: [EMAIL PROTECTED]
exposed-modules: 
Graphics.Plot.Display, 
Graphics.Plot.Picture, 
Graphics.Plot.Primitive, 
Graphics.Plot.Render, 
Graphics.Plot.Colors,
Graphics.Plot.Util,
Graphics.Plot.RenderState,
Graphics.Plot.Animate,
Graphics.Plot.View,
Graphics.Plot.Wrapper,
Graphics.Plot
Build-Depends:  base, OpenGL, GLUT
ghc-options: -fglasgow-exts

and then tried 
runhaskell Setup.hs configure
runhaskell Setup.hs build
runhaskell Setup.hs install

which all seemed to work fine (see log below).

However, when building an example that uses that package, I get a lot of
linker errors (see log below)

Is this because I configured the cabal files incorrectly, or do I have to
adjust the module sources so they explicitly export the missing symbols?

Thanks,
Peter

-- LOG ---

L:\3rdParty\ANUPlot\srcrunhaskell Setup.hs unregister 
Unregistering Plot-1.1...
Saving old package config file... done.
Writing new package config file... done.

L:\3rdParty\ANUPlot\srcrunhaskell Setup.hs clean 
cleaning...

L:\3rdParty\ANUPlot\srcrunhaskell Setup.hs configure --global 
Configuring Plot-1.1...
configure: Dependency base-any: using base-2.1.1
configure: Dependency OpenGL-any: using OpenGL-2.2.1
configure: Dependency GLUT-any: using GLUT-2.1.1
configure: Using install prefix: C:\Program Files
configure: Binaries installed in: C:\Program Files\Haskell\bin
configure: Libraries installed in: C:\Program
Files\Haskell\Plot-1.1\ghc-6.6.1
configure: Private binaries installed in: C:\Program Files\Plot-1.1
configure: Data files installed in: C:\Program Files\Common Files\Plot-1.1
configure: Using compiler: c:\app\ghc\bin\ghc.exe
configure: Compiler flavor: GHC
configure: Compiler version: 6.6.1
configure: Using package tool: c:\app\ghc\bin\ghc-pkg.exe
configure: Using ar found on system at: c:\app\ghc\bin\ar.exe
configure: No haddock found
configure: No pfesetup found
configure: No ranlib found
configure: Using runghc found on system at: c:\app\ghc\bin\runghc.exe
configure: No runhugs found
configure: No happy found
configure: No alex found
configure: Using hsc2hs: c:\app\ghc\bin\hsc2hs.exe
configure: No c2hs found
configure: No cpphs found
configure: No greencard found

L:\3rdParty\ANUPlot\srcrunhaskell Setup.hs build 
Preprocessing library Plot-1.1...
Building Plot-1.1...

L:\3rdParty\ANUPlot\srcrunhaskell Setup.hs register 
Registering Plot-1.1...
Reading package info from .installed-pkg-config ... done.
Saving old package config file... done.
Writing new package config file... done.

L:\3rdParty\ANUPlot\srcrunhaskell Setup.hs install 
Installing: C:\Program Files\Haskell\Plot-1.1\ghc-6.6.1  C:\Program
Files\Haskell\bin Plot-1.1...
Registering Plot-1.1...
Reading package info from .installed-pkg-config ... done.
Saving old package config file... done.
Writing new package config file... done.

Linking AnimClock.exe ...
C:\Program
Files\Haskell\Plot-1.1\ghc-6.6.1/libHSPlot-1.1.a(Wrapper.o)(.text+0x2f1):fak
e: undefined reference to
`Plotzm1zi1_GraphicsziPlotziCallback_Display_con_info'
C:\Program
Files\Haskell\Plot-1.1\ghc-6.6.1/libHSPlot-1.1.a(Wrapper.o)(.text+0xc7c):fak
e: undefined reference to `Plotzm1zi1_GraphicsziPlotziUtilOp_zhzh_closure'
C:\Program
Files\Haskell\Plot-1.1\ghc-6.6.1/libHSPlot-1.1.a(Wrapper.o)(.text+0xdcb):fak
e: undefined reference to
`Plotzm1zi1_GraphicsziPlotziCallback_Idle_con_info'
C:\Program
Files\Haskell\Plot-1.1\ghc-6.6.1/libHSPlot-1.1.a(Wrapper.o)(.text+0xdfc):fak
e: undefined reference to
`Plotzm1zi1_GraphicsziPlotziCallback_Display_con_info'
C:\Program
Files\Haskell\Plot-1.1\ghc-6.6.1/libHSPlot-1.1.a(Wrapper.o)(.text+0xe3b):fak
e: undefined reference to
`Plotzm1zi1_GraphicsziPlotziCallback_Display_con_info'
C:\Program
Files\Haskell\Plot-1.1\ghc-6.6.1/libHSPlot-1.1.a(Wrapper.o)(.text+0xe68):fak
e: undefined reference to
`Plotzm1zi1_GraphicsziPlotziCallback_Display_con_info'
C:\Program
Files\Haskell\Plot-1.1\ghc-6.6.1/libHSPlot-1.1.a(Wrapper.o)(.rodata+0x54):fa
ke: undefined reference to `Plotzm1zi1_GraphicsziPlotziUtilOp_zhzh_closure'
C:\Program
Files\Haskell\Plot-1.1\ghc-6.6.1/libHSPlot-1.1.a(RenderState.o)(.text+0x3d6)
:fake: undefined reference to
`Plotzm1zi1_GraphicsziPlotziUtilOp_zlzhzhzg_closure'
C:\Program
Files\Haskell\Plot-1.1\ghc-6.6.1/libHSPlot-1.1.a(RenderState.o)(.text+0x652)
:fake: undefined reference to
`Plotzm1zi1_GraphicsziPlotziUtilOp_zlzhzhzg_closure'
C:\Program
Files\Haskell\Plot-1.1\ghc-6.6.1/libHSPlot-1.1.a(RenderState.o)(.text+0x8ce)
:fake: undefined reference to
`Plotzm1zi1_GraphicsziPlotziUtilOp_zlzhzhzg_closure'
C:\Program

Re: [Haskell-cafe] How to fix linker errors when creating a package using cabal

2007-08-25 Thread Malte Milatz
Peter Verswyvelen:
 However, when building an example that uses that package, I get a lot of
 linker errors (see log below)

What options did you use when compiling the example?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] RE: Re: Remember the future

2007-08-25 Thread Benjamin Franksen
Simon Peyton-Jones wrote:
 | From the ghc manual:
 |
 | ---
 | 7.3.3. The recursive do-notation
 | ...
 
 |
 | It is unfortunate that the manual does not give the translation rules,
or at
 | least the translation for the given example.
 
 Hmm.  OK.  I've improved the manual with a URL to the main paper
 http://citeseer.ist.psu.edu/erk02recursive.html
 which is highly readable. And I've given the translation for the example
as you suggest

After finally reading the paper I agree that repeating the translation in
teh manual is not a good idea. However, I suggest the manual should mention
the restrictions imposed for mdo (wrt the normal do)

 * no shadowing allowed for generator bound variables
 * let bindings must be monomorphic

Both of them might cause confusion if someone hits them by accident and
starts to wonder what's wrong with her code, in which case it would be
helpful if this information were directly available in teh manual. No need
to give a detailed rationale (that's what the paper can be read for), just
say that they are there.

BTW, I agree with the paper that the restrictions are sensible and typically
don't hurt.

Thanks
Ben

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


RE: [Haskell-cafe] How to fix linker errors when creating a package using cabal

2007-08-25 Thread Peter Verswyvelen
Oops, I forget to paste that in.

Just 

GHC --make AnimClock.hs

with 

ANUPlot\src\Demo

As the current directory.

-Original Message-
From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of Malte Milatz
Sent: Saturday, August 25, 2007 12:11 PM
To: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] How to fix linker errors when creating a package
using cabal

Peter Verswyvelen:
 However, when building an example that uses that package, I get a lot of
 linker errors (see log below)

What options did you use when compiling the example?
___
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] Re: Haskellnet could not find network-any dependency.

2007-08-25 Thread Benjamin Franksen
Edward Ing wrote:
 Hi,
 I am trying to install Haskellnet. But the configuration breaks on
 dependency of network-any in GHC 6.6.
 
 I thought network-any was part of Hierarchical libraries?
 
 If not where do I get it?

The generic place for libraries nowadays is hackage:
http://hackage.haskell.org/packages/archive/pkg-list.html where you find
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/network-2.0

The 'Hierarchical Libraries' do not exist as such; all modern Haskell
libraries use the hierarchical module name extension for their exported
modules. There are, however, a certain number of libraries that are
regularly shipped together with Haskell implementations. All of them,
except those which work only together with a certain compiler/interpreter
version (e.g. 'base'), are avaiable from hackage.

BTW, it would be nice if hackage would list repository locations, too, if
available. The one for 'network' library is not mentioned on hackage; I
found one here: http://darcs.haskell.org/packages/network/

Cheers
Ben

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


Re: [Haskell-cafe] Ideas

2007-08-25 Thread Neil Mitchell
Hi

 - Blogging software. (Because there isn't enough of it in the world yet.)

Hope (google: Haskell Hope)

 - A wiki program. (Ditto.)

Flippi (google: Haskell Flippi)

 - A general CMS.

Hope

 - An interactive function plotter. (GNUplot is nice, but it can't plot
 recursive functions...)

None that I know of.

 - A graphical programming tool. (You add boxes and put in lines, it
 constructs a program that you can run.)

You mean a programming tool with a horrible syntax and user interface?
If you want to remove the joy from programming, just use Ada.

Alternatively, use PureData, which can be extended with Haskell, and
gives boxes and lines.
http://haskell.org/haskellwiki/AngloHaskell/2007#Abstracts

Thanks

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


Re: [Haskell-cafe] Ideas

2007-08-25 Thread Andrew Coppin

Neil Mitchell wrote:



- A wiki program. (Ditto.)



Flippi (google: Haskell Flippi)
  


...and yet haskell.org uses WikiMedia? (Which is written in something 
bizzare like Perl...)



- A general CMS.



Hope
  


Woo! I'll have to go play with this for a while...


- An interactive function plotter. (GNUplot is nice, but it can't plot
recursive functions...)



None that I know of.
  


Mmm, OK. I would have thought it would be a nice project for somebody...


- A graphical programming tool. (You add boxes and put in lines, it
constructs a program that you can run.)



You mean a programming tool with a horrible syntax and user interface?
  


LOL! That's not entirely what I meant... ;-)

Have you ever played with KLogic? You draw boxes and lines, and it makes 
some logic. (As in the digital electronics sense of logic.)


I have some (very expensive) software called Reaktor. You draw boxes and 
lines, it does DSP algorithms. You build synthesizers and effects boxes 
with it.


You get the idea.

(The trouble with KLogic is its utter buggyness... I'd love to have a 
tool like it that actually works properly!)



If you want to remove the joy from programming, just use Ada.
  


Or Perl. Or Java. Or C. Or C++. Or VB. Or...


Alternatively, use PureData, which can be extended with Haskell, and
gives boxes and lines.
http://haskell.org/haskellwiki/AngloHaskell/2007#Abstracts
  


OK, I'll take a cool.

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


Re: [Haskell-cafe] Ideas

2007-08-25 Thread Neil Mitchell
Hi

  Flippi (google: Haskell Flippi)

 ...and yet haskell.org uses WikiMedia? (Which is written in something
 bizzare like Perl...)

Yes, but WikiMedia is a result of years of work, Flippi is a lot less.
Wikipedia uses WikiMedia - its a tried and proven solution.

  - A graphical programming tool. (You add boxes and put in lines, it
  constructs a program that you can run.)

 Have you ever played with KLogic? You draw boxes and lines, and it makes
 some logic. (As in the digital electronics sense of logic.)

 I have some (very expensive) software called Reaktor. You draw boxes and
 lines, it does DSP algorithms. You build synthesizers and effects boxes
 with it.

That sounds exactly like PureData - you can also do graphics as well
with PureData, the demo I saw was very cool. Of course, PureData is
written in C with Haskell as an extension language.

The last two ideas you mentioned require a graphical user interface,
which is an area of Haskell which is comparatively weak, compared to
the rest of Haskell.

Thanks

Neil


PS: Apologies to Andrew for 2 copies of this message.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Ideas

2007-08-25 Thread Philippa Cowderoy
On Sat, 25 Aug 2007, Andrew Coppin wrote:

 Neil Mitchell wrote:
  
   - A wiki program. (Ditto.)
   
  
  Flippi (google: Haskell Flippi)

 
 ...and yet haskell.org uses WikiMedia? (Which is written in something 
 bizzare like Perl...)
 

Flippi is... rather minimalistic. And fugly. You can tell it was written 
by someone who has trouble getting things done! I get the impression it 
did a certain amount of good as a proof of concept and a reminder that 
doing things the old-fashioned way still works though.

   - A general CMS.
   
  
  Hope

 
 Woo! I'll have to go play with this for a while...
 

While I haven't looked at it much, Hope's seeing a lot more actual use.

-- 
[EMAIL PROTECTED]

Society does not owe people jobs.
Society owes it to itself to find people jobs.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Ideas

2007-08-25 Thread Philippa Cowderoy
On Sat, 25 Aug 2007, Neil Mitchell wrote:

 Hi
 
   Flippi (google: Haskell Flippi)
 
  ...and yet haskell.org uses WikiMedia? (Which is written in something
  bizzare like Perl...)
 
 Yes, but WikiMedia is a result of years of work, Flippi is a lot less.

The original version was the result of a certain amount of thinking, an 
overnight hack and a few tweaks :-)

  Have you ever played with KLogic? You draw boxes and lines, and it makes
  some logic. (As in the digital electronics sense of logic.)
 
  I have some (very expensive) software called Reaktor. You draw boxes and
  lines, it does DSP algorithms. You build synthesizers and effects boxes
  with it.
 
 That sounds exactly like PureData - you can also do graphics as well
 with PureData, the demo I saw was very cool. Of course, PureData is
 written in C with Haskell as an extension language.
 

Reaktor is rather nicer to use than PureData though, in that it's designed 
to work with mainstream sequencers (or any VST - I work with trackers 
myself) and be used by non-hackers. Also, I'm not entirely sure it's fair 
to say that it has Haskell as an extension language as such - but Claude's 
slides'll give a better explanation than I can.

 The last two ideas you mentioned require a graphical user interface,
 which is an area of Haskell which is comparatively weak, compared to
 the rest of Haskell.
 

Yep. It would be nice to have a library for doing that kind of stuff 
though, I suspect there're many nifty projects that would be easy to 
implement once that was done - Haskell's good at manipulating the 
underlying structures.

-- 
[EMAIL PROTECTED]

The reason for this is simple yet profound. Equations of the form
x = x are completely useless. All interesting equations are of the
form x = y. -- John C. Baez
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] How to fix linker errors when creating a package using cabal

2007-08-25 Thread Peter Verswyvelen
Indeed, adding the non-exposed modules to the other-modules fixed it.

Thanks Allan!

Cheers,
Peter

-Original Message-
From: Allan Clark [mailto:[EMAIL PROTECTED] 
Sent: Saturday, August 25, 2007 2:28 PM
To: Peter Verswyvelen
Subject: Re: [Haskell-cafe] How to fix linker errors when creating a package
using cabal

Peter Verswyvelen wrote:
 I'm trying to make a package of Ben.Lippmeier's very nice ANUPlot graphics
 library (http://cs.anu.edu.au/people/Ben.Lippmeier)

 IMHO this would be a great contribution to the Haskell library, it's very
 clean code for newbies :)

 I created the following cabal file:

 name: Plot
 version: 1.1
 license: AllRightsReserved
 maintainer: [EMAIL PROTECTED]
 exposed-modules: 
   Graphics.Plot.Display, 
   Graphics.Plot.Picture, 
   Graphics.Plot.Primitive, 
   Graphics.Plot.Render, 
   Graphics.Plot.Colors,
   Graphics.Plot.Util,
   Graphics.Plot.RenderState,
   Graphics.Plot.Animate,
   Graphics.Plot.View,
   Graphics.Plot.Wrapper,
   Graphics.Plot
 Build-Depends:  base, OpenGL, GLUT
 ghc-options: -fglasgow-exts

 and then tried 
 runhaskell Setup.hs configure
 runhaskell Setup.hs build
 runhaskell Setup.hs install

 which all seemed to work fine (see log below).

 However, when building an example that uses that package, I get a lot of
 linker errors (see log below)

 Is this because I configured the cabal files incorrectly, or do I have to
 adjust the module sources so they explicitly export the missing symbols?

 Thanks,
 Peter
 [ snip ]

Files\Haskell\Plot-1.1\ghc-6.6.1/libHSPlot-1.1.a(Wrapper.o)(.text+0x2f1):fak
 e: undefined reference to
 `Plotzm1zi1_GraphicsziPlotziCallback_Display_con_info'
   
Hi, I'm not cabal expert, but basically I had a similar problem, and I 
fixed it by adding a missing module in the 'exposed-modules' part. 
Basically where is con_info defined, it's probably in a module which 
isn't exposed.
If so then either put it in the 'exposed-modules' section or if you do 
not wish to expose it then maybe you could try putting it in a 
'other-modules' section.

regards
allan


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


RE: [Haskell-cafe] Ideas

2007-08-25 Thread Peter Verswyvelen
 - A graphical programming tool. (You add boxes and put in lines, it
 constructs a program that you can run.)

 You mean a programming tool with a horrible syntax and user interface?
 If you want to remove the joy from programming, just use Ada.

For programmers or scientists, I agree. 

For designers/artists who want to make cool stuff without learning a textual
programming language, I totally disagree. Look at Apple Shake, SideFX
Houdini, Werkzeug, Shader FX, Unreal 3, or even National Instruments
Labview, and more... They all have a (albeit very limited) visual
programming language. People get real procedural work done with these
tools. Almost every 3D movie uses at least one of tools I mentioned.

Peter



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


[Haskell-cafe] Question of a manual computation on Reader Monad.

2007-08-25 Thread Peter Cai
Hi all,

In order to improve my understanding of monad, I am trying to do some manual
computation on Reader Monad but I got some problem.

The computation is like this:

--instance Monad (Reader e) where
--return a = Reader $ \e - a
--(Reader r) = f = Reader $ \e - f (r e) e

runReader (do { b - Reader $ show; return b } )  -- This is the initial
expression, it should equals show

runReader (Reader $ show = \b - return b)   -- remove do notion

runReader (Reader $ \e - return( show e ) e)  -- apply the definition of
=

runReader (Reader $ \e - (Reader $ \e1 - show(e)) e)  -- apply the
definition of return

But the last expression is incorrect, and I don't know how to go on.

Could anyone explain this for me?

Thanks in advance!

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


Re: [Haskell-cafe] Question of a manual computation on Reader Monad.

2007-08-25 Thread Malte Milatz
Peter Cai:
 Hi all,
 
 In order to improve my understanding of monad, I am trying to do some manual
 computation on Reader Monad but I got some problem.
 
 The computation is like this:
 
 --instance Monad (Reader e) where
 --return a = Reader $ \e - a
 --(Reader r) = f = Reader $ \e - f (r e) e

This cannot work out because this definition is ill-typed, which you
will notice if you try to compile it (or if you contemplate about what
the type of (f (r e) e) is). Here is a way to define a reader monad:

newtype Reader e a = Reader { runReader :: (e - a) }

instance Monad (Reader e) where
return a= Reader $ \_ - a
Reader r = f  = Reader $ \e - runReader (f (r e)) e

You can then do your calculation like this:

Reader show = return
=   Reader $ \e - runReader (return (show e)) e
=   Reader $ \e - runReader (Reader (\_ - show e)) e
=   Reader $ \e - (\_ - show e) e
=   Reader $ \e - show e
=   Reader show;

-- Note that, except for the use of “show” as a specific
-- example, the above is equivalent to proving that the
-- second monad law holds for (Reader e).

runReader (Reader show = return) 
=   runReader (Reader show)
=   show.

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


Re: [Haskell-cafe] Question of a manual computation on Reader Monad.

2007-08-25 Thread Kim-Ee Yeoh


一首诗 wrote:
 
 runReader (do { b - Reader $ show; return b } )  -- This is the initial
 expression, it should equals show
 
 runReader (Reader $ show = \b - return b)   -- remove do notion
 

I'm not sure that's the right un-do-ization. It so happens that the 
exponent monad ((-) r) and the Reader monads are semantically 
identically. Is this a homework question?


一首诗 wrote:
 
 runReader (Reader $ \e - return( show e ) e)  -- apply the definition of
 =
 
 runReader (Reader $ \e - (Reader $ \e1 - show(e)) e)  -- apply the
 definition of return
 
 But the last expression is incorrect, and I don't know how to go on.
 

-- 
View this message in context: 
http://www.nabble.com/Question-of-a-manual-computation-on-Reader-Monad.-tf4328025.html#a12326875
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] newbie - how to call a Haskell interpreter from C

2007-08-25 Thread Brock Peabody
On 8/25/07, Henk-Jan van Tuyl [EMAIL PROTECTED] wrote:


 The easiest way to run Haskell software from a C program is to give the
 shell command:
runhaskell Foo.hs


I'm a newbie but not that new :) I really have to be able to interpret the
Haskell from within the same process.

A more advanced way is, to link Haskell libraries by means of the foreign
 function interface (FFI) [1].
 There are several tools to support FFI development [2]. I am sure my list
 of URL's is not complete.

 [1] http://www.cse.unsw.edu.au/~chak/haskell/ffi/
 http://www.cse.unsw.edu.au/%7Echak/haskell/ffi/
  http://www.haskell.org/haskellwiki/FFI_Introduction
  http://www.haskell.org/haskellwiki/FFI_cook_book

 [2] http://www.haskell.org/haskellwiki/FFI_imports_packaging_utility
  http://www.haskell.org/haskellwiki/HSFFIG


My understanding is that FFI helps you to call into other languages from
Haskell and vice-versa. I will definitely need this, but what I can't figure
out how to do is to invoke the ghci or hugs interpreter programmatically,
in-process. I didn't see a way to do that in the links you listed, am I
missing something?

Much thanks,
Brock Peabody
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] newbie - how to call a Haskell interpreter from C

2007-08-25 Thread Stefan O'Rear
On Sat, Aug 25, 2007 at 12:34:45PM -0400, Brock Peabody wrote:
 On 8/25/07, Henk-Jan van Tuyl [EMAIL PROTECTED] wrote:
 
 
  The easiest way to run Haskell software from a C program is to give the
  shell command:
 runhaskell Foo.hs
 
 
 I'm a newbie but not that new :) I really have to be able to interpret the
 Haskell from within the same process.
 
  A more advanced way is, to link Haskell libraries by means of the foreign
  function interface (FFI) [1].
  There are several tools to support FFI development [2]. I am sure my list
  of URL's is not complete.
 
  [1] http://www.cse.unsw.edu.au/~chak/haskell/ffi/
  http://www.cse.unsw.edu.au/%7Echak/haskell/ffi/
   http://www.haskell.org/haskellwiki/FFI_Introduction
   http://www.haskell.org/haskellwiki/FFI_cook_book
 
  [2] http://www.haskell.org/haskellwiki/FFI_imports_packaging_utility
   http://www.haskell.org/haskellwiki/HSFFIG
 
 
 My understanding is that FFI helps you to call into other languages from
 Haskell and vice-versa. I will definitely need this, but what I can't figure
 out how to do is to invoke the ghci or hugs interpreter programmatically,
 in-process. I didn't see a way to do that in the links you listed, am I
 missing something?

No, you're not missing anything, and there are no deliberately
embeddable Haskell interpreters.  Your options are:

1a. GHC, native code:

Link libHSplugins.a into your program (compile Don's hs-plugins
library).  Then call the external functions described in
http://www.cse.unsw.edu.au/~dons/hs-plugins/hs-plugins-Z-H-4.html#node_sec_7.2,

Pro: Full GHC runtime speed

Con: Full GHC compile-time sloth
 As big as GHC (20mbytes file size)
 Leaks memory

1b. GHC, bytecode:

Write a binding to the GHC-API runStmt function.  foreign export it.

Pro: As fast as GHCi
 No leaks

Con: Still huge
 Slow runtime

2. Hugs

Link Hugs.  Study the source code to runhugs.

Pro: Much faster loading
 Much smaller footprint

Con: Less polished
 Slow runtime

Stefan


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


Re: [Haskell-cafe] Ideas

2007-08-25 Thread Andrew Coppin

Bertram Felgenhauer wrote:

Hi,

You wrote:
  
- An interactive function plotter. (GNUplot is nice, but it can't plot 
recursive functions...)



Actually you can express a lot of those with the ?: operator.
  


Ooo... interesting. I don't recall seeing *that* in the manual!


gnuplot f(x) = x  1 ? 0 : f(x/2) + 1
gnuplot plot f(x)

works just as expected. Mutually recursive functions defined that
way work, too.

Still, support could be a lot better here.
  


OK... so how do I plot a graph of the Fibonacci numbers?

Similarly, how do I plot (what Haskell calls) interate f 0?

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


[Haskell-cafe] Parsec is being weird at me

2007-08-25 Thread Andrew Coppin

Anybody want to explain to me why this doesn't work?

  ___ ___ _
 / _ \ /\  /\/ __(_)
/ /_\// /_/ / /  | |  GHC Interactive, version 6.6.1, for Haskell 98.
/ /_\\/ __  / /___| |  http://www.haskell.org/ghc/
\/\/ /_/\/|_|  Type :? for help.

Loading package base ... linking ... done.
Prelude :m Text.ParserCombinators.Parsec
Prelude Text.ParserCombinators.Parsec parseTest (endBy anyToken (char 
'#')) abc#

Loading package parsec-2.0 ... linking ... done.
parse error at (line 1, column 1):
unexpected b
expecting #

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


Re: [Haskell-cafe] Ideas

2007-08-25 Thread Andrew Coppin

Neil Mitchell wrote:

HI

  

Flippi (google: Haskell Flippi)
  

...and yet haskell.org uses WikiMedia? (Which is written in something
bizzare like Perl...)



Yes, but WikiMedia is a result of years of work, Flippi is a lot less.
Wikipedia uses WikiMedia - its a tried and proven solution.
  


Well, I guess...

I just thought, you know, the Tcl wiki is written in Tcl, why isn't the 
Haskell wiki written in Haskell? Hey, aren't we trying to tell people is 
a *useful* language that people should learn and use? ;-)



- A graphical programming tool. (You add boxes and put in lines, it
constructs a program that you can run.)


Have you ever played with KLogic? You draw boxes and lines, and it makes
some logic. (As in the digital electronics sense of logic.)

I have some (very expensive) software called Reaktor. You draw boxes and
lines, it does DSP algorithms. You build synthesizers and effects boxes
with it.



That sounds exactly like PureData - you can also do graphics as well
with PureData, the demo I saw was very cool. Of course, PureData is
written in C with Haskell as an extension language.
  


Oh. Ah well..


The last two ideas you mentioned require a graphical user interface,
which is an area of Haskell which is comparatively weak, compared to
the rest of Haskell.
  


Yeah, I noticed. Though actually Gtk2hs isn't too bad. (There's a few 
corners that require bit-flipping and other low-level strangeness...)


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


Re: [Haskell-cafe] Ideas

2007-08-25 Thread Andrew Coppin

Philippa Cowderoy wrote:
Flippi is... rather minimalistic. And fugly. You can tell it was written 
by someone who has trouble getting things done! I get the impression it 
did a certain amount of good as a proof of concept and a reminder that 
doing things the old-fashioned way still works though.
  


Ah yes, nothing like a good proof-of-concept implementation. Except that 
you usually can't do any real stuff with it. ;-)


Some of you may remember a few years back, it seemed that Java was a 
programming language invented for implementing Tic-Tac-Toe programs...


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


Re: [Haskell-cafe] Ideas

2007-08-25 Thread Andrew Coppin

Philippa Cowderoy wrote:

I have some (very expensive) software called Reaktor. You draw boxes and
lines, it does DSP algorithms. You build synthesizers and effects boxes
with it.
  

That sounds exactly like PureData - you can also do graphics as well
with PureData, the demo I saw was very cool. Of course, PureData is
written in C with Haskell as an extension language.



Reaktor is rather nicer to use than PureData though, in that it's designed 
to work with mainstream sequencers (or any VST - I work with trackers 
myself) and be used by non-hackers. Also, I'm not entirely sure it's fair 
to say that it has Haskell as an extension language as such - but Claude's 
slides'll give a better explanation than I can.
  


Reaktor has a few limitations though.

1. It's virtually impossible to debug the thing! (I.e., if your synth 
doesn't work... good luck working out why.)


2. It lacks looping capabilities. For example, you cannot build a 
variable-size convolution block - only a fixed-size one. (If you want to 
draw *a lot* of wires!) If you look through the standard library, you'll 
find no end of instruments that use a hack of using voice polyphony to 
crudely simulate looping... but it's not too hot.


Would be nice if I could build something in Haskell that overcomes 
these. OTOH, does Haskell have any way to talk to the audio hardware?


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


Re: [Haskell-cafe] Ideas

2007-08-25 Thread Brandon S. Allbery KF8NH


On Aug 25, 2007, at 14:43 , Andrew Coppin wrote:


Neil Mitchell wrote:

HI



Flippi (google: Haskell Flippi)

...and yet haskell.org uses WikiMedia? (Which is written in  
something

bizzare like Perl...)



Yes, but WikiMedia is a result of years of work, Flippi is a lot  
less.

Wikipedia uses WikiMedia - its a tried and proven solution.



Well, I guess...

I just thought, you know, the Tcl wiki is written in Tcl, why isn't  
the Haskell wiki written in Haskell? Hey, aren't we trying to tell  
people is a *useful* language that people should learn and use? ;-)


Are you volunteering to take the time to write and test it?

--
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] Ideas

2007-08-25 Thread Andrew Coppin

C.M.Brown wrote:

- A graphical programming tool. (You add boxes and put in lines, it
constructs a program that you can run.)



I'm not entirely exactly sure what you mean by this.


I wasn't especially specific about it, that's true enough. I actually 
had several different things in mind...



If you mean one can
create programs by creating them visually then perhaps you could consider
Vital:

http://www.cs.kent.ac.uk/projects/vital/

It's a document-centered implementation of Haskell. Allowing one to
display and directly manipulate Haskell data structures in real-time.
  


Looks very interesting... and very low-tech visuals. :-/

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


Re: [Haskell-cafe] Ideas

2007-08-25 Thread Andrew Coppin

Brandon S. Allbery KF8NH wrote:


On Aug 25, 2007, at 14:43 , Andrew Coppin wrote:


Yes, but WikiMedia is a result of years of work, Flippi is a lot less.
Wikipedia uses WikiMedia - its a tried and proven solution.



Well, I guess...

I just thought, you know, the Tcl wiki is written in Tcl, why isn't 
the Haskell wiki written in Haskell? Hey, aren't we trying to tell 
people is a *useful* language that people should learn and use? ;-)


Are you volunteering to take the time to write and test it?


Are you offering to pay me? :-D

Oh, wait, volunteer...




Well, let's put it this way: If I ever get round to making something and 
it turns out to be any good, you're free to use it... Don't hold your 
breath... ;-)


PS. Do paid Haskell jobs really exist?

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


Re: [Haskell-cafe] Ideas

2007-08-25 Thread Iain Lane
 - Blogging software. (Because there isn't enough of it in the world yet.)

In addition (because a little competition can't help ;), I'm going to
be experimenting with writing a blog engine for my final year project
at Uni next year - 2007/08. Hopefully some good will come of it, i.e.
something that people (I) can actually use. It'll probably be more
blog less CMS than Hope. At the minute I'm looking at using HAppS for
most of it. Should be fun!

Iain

ps. Sorry for the spam Andrew.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Ideas

2007-08-25 Thread Andrew Coppin

Iain Lane wrote:

- Blogging software. (Because there isn't enough of it in the world yet.)



In addition (because a little competition can't help ;), I'm going to
be experimenting with writing a blog engine for my final year project
at Uni next year - 2007/08. Hopefully some good will come of it, i.e.
something that people (I) can actually use. It'll probably be more
blog less CMS than Hope. At the minute I'm looking at using HAppS for
most of it. Should be fun!
  


Good luck with that - should be enjoyable at least. ;-)

I'm going to have a go at it myself as well. My current blog uses 
something called word press, and I don't like it especially much. (It 
*insists* on chewing up all my carefully applied formatting. And the 
people providing it have locked it down so there's loads I can't 
change...) So I'm hoping to write something nice to replace it with. But 
we'll see...


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


Re: [Haskell-cafe] Parsec is being weird at me

2007-08-25 Thread Albert Y. C. Lai

Andrew Coppin wrote:

Prelude :m Text.ParserCombinators.Parsec
Prelude Text.ParserCombinators.Parsec parseTest (endBy anyToken (char 
'#')) abc#

Loading package parsec-2.0 ... linking ... done.
parse error at (line 1, column 1):
unexpected b
expecting #


I read the doc and determined that it is perfectly correct behaviour.

Hint: anyToken becomes anyChar because your input is [Char].
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Ideas

2007-08-25 Thread Stefan O'Rear
On Sat, Aug 25, 2007 at 07:43:30PM +0100, Andrew Coppin wrote:
 Neil Mitchell wrote:
 HI

   
 Flippi (google: Haskell Flippi)
   
 ...and yet haskell.org uses WikiMedia? (Which is written in something
 bizzare like Perl...)
 

 Yes, but WikiMedia is a result of years of work, Flippi is a lot less.
 Wikipedia uses WikiMedia - its a tried and proven solution.
   

 Well, I guess...

 I just thought, you know, the Tcl wiki is written in Tcl, why isn't the 
 Haskell wiki written in Haskell? Hey, aren't we trying to tell people is a 
 *useful* language that people should learn and use? ;-)

Actually, we aren't.  You might not have been able to tell, but a core
goal of our community is to stay small and avoid success at all costs;
our language is not practical, not designed to be practical, and if it
ever becomes practical, it will have done so only by a terrible streak
of bad luck.  Remember, success breeds inertia, and inertia would ruin
our fundamental goal of being an agile research language.

:)

Stefan


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


[Haskell-cafe] Re: Parsec is being weird at me

2007-08-25 Thread ChrisK
Andrew Coppin wrote:
 Anybody want to explain to me why this doesn't work?
 
   ___ ___ _
  / _ \ /\  /\/ __(_)
 / /_\// /_/ / /  | |  GHC Interactive, version 6.6.1, for Haskell 98.
 / /_\\/ __  / /___| |  http://www.haskell.org/ghc/
 \/\/ /_/\/|_|  Type :? for help.
 
 Loading package base ... linking ... done.
 Prelude :m Text.ParserCombinators.Parsec
 Prelude Text.ParserCombinators.Parsec parseTest (endBy anyToken (char
 '#')) abc#
 Loading package parsec-2.0 ... linking ... done.
 parse error at (line 1, column 1):
 unexpected b
 expecting #

anyToken is singular: it accepts a single token, in this case 'a'.

Then endBy expects (char '#') to match and reads 'b' instead and gives the error
message.

So using (many anyToken) gets further:

 Prelude Text.ParserCombinators.Parsec parseTest (endBy (many anyToken) (char 
 '#')) abc#
 Loading package parsec-2.0 ... linking ... done.
 parse error at (line 1, column 1):
 unexpected end of input
 expecting #
 Prelude Text.ParserCombinators.Parsec parseTe

Here (many anyToken) reads all of abc# and then endBy wants to read (char '#')
and get the end of input instead.

So the working version of endBy is thus:

 Prelude Text.ParserCombinators.Parsec parseTest (endBy (many (noneOf #)) 
 (char '#')) abc#
 [abc]

Or you may need to not use endBy...

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


Re: [Haskell-cafe] Ideas

2007-08-25 Thread Andrew Coppin

Stefan O'Rear wrote:

On Sat, Aug 25, 2007 at 07:43:30PM +0100, Andrew Coppin wrote:
  
Hey, aren't we trying to tell people is a 
*useful* language that people should learn and use? ;-)



Actually, we aren't.  You might not have been able to tell, but a core
goal of our community is to stay small and avoid success at all costs;
our language is not practical, not designed to be practical, and if it
ever becomes practical, it will have done so only by a terrible streak
of bad luck.  Remember, success breeds inertia, and inertia would ruin
our fundamental goal of being an agile research language.
  


Heh. Well, that told me... o_O

Maybe *this* is why everybody else thinks I'm an idiot for using 
Haskell... :-(


PS. Wasn't one of the explicit design goals to design a standardised 
language for teaching FP?


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


[Haskell-cafe] Re: Parsec is being weird at me

2007-08-25 Thread Andrew Coppin

ChrisK wrote:

Andrew Coppin wrote:
  

Anybody want to explain to me why this doesn't work?

  ___ ___ _
 / _ \ /\  /\/ __(_)
/ /_\// /_/ / /  | |  GHC Interactive, version 6.6.1, for Haskell 98.
/ /_\\/ __  / /___| |  http://www.haskell.org/ghc/
\/\/ /_/\/|_|  Type :? for help.

Loading package base ... linking ... done.
Prelude :m Text.ParserCombinators.Parsec
Prelude Text.ParserCombinators.Parsec parseTest (endBy anyToken (char
'#')) abc#
Loading package parsec-2.0 ... linking ... done.
parse error at (line 1, column 1):
unexpected b
expecting #



anyToken is singular: it accepts a single token, in this case 'a'.

Then endBy expects (char '#') to match and reads 'b' instead and gives the error
message.

So using (many anyToken) gets further:

  

Prelude Text.ParserCombinators.Parsec parseTest (endBy (many anyToken) (char '#')) 
abc#
Loading package parsec-2.0 ... linking ... done.
parse error at (line 1, column 1):
unexpected end of input
expecting #
Prelude Text.ParserCombinators.Parsec parseTe



Here (many anyToken) reads all of abc# and then endBy wants to read (char '#')
and get the end of input instead.

So the working version of endBy is thus:

  

Prelude Text.ParserCombinators.Parsec parseTest (endBy (many (noneOf #)) (char '#')) 
abc#
[abc]



Or you may need to not use endBy...
  


But hang on a minute...

many parses 0 or more occurrances of an item.

sepBy parses 0 or more occurrances of an item, seperated by another item.

endBy parses 0 or more occurrances of an item, terminated by another item.

sepEndBy parses 0 or more occurrances of an item, seperated *and* 
terminated by another item.


...except that endBy doesn't seem to be working right. :-S

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


Re: [Haskell-cafe] Ideas

2007-08-25 Thread Andrew Coppin

Andrew Coppin wrote:

C.M.Brown wrote:

If you mean one can
create programs by creating them visually then perhaps you could 
consider

Vital:

http://www.cs.kent.ac.uk/projects/vital/

It's a document-centered implementation of Haskell. Allowing one to
display and directly manipulate Haskell data structures in real-time.
  


Looks very interesting... and very low-tech visuals. :-/


Hang on a minute... it's written in Java... and it can run Haskell 
code...? o_O


Now that's interesting! (Re. the other thread about we should have an 
automatic expression reducing program...)


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


RE: [Haskell-cafe] Ideas

2007-08-25 Thread Peter Verswyvelen
 *useful* language that people should learn and use? ;-)

Actually, we aren't.  You might not have been able to tell, 
but a core goal of our community is to stay small and avoid 
success at all costs; our language is not practical, 
not designed to be practical, and if it ever becomes practical, 
it will have done so only by a terrible streak of bad luck.  
Remember, success breeds inertia, and inertia would ruin 
our fundamental goal of being an agile research language.

Well, IMHO the only reasons why Haskell is not a language for the masses
are:

- No marketing. If a company as big as Microsoft would decide that Haskell
is to become the standard language, then it would be so.

- Ancient IDEs. When someone comes from Eclipse or Visual Studio it feels
one is teleported back to the stone ages. Although Visual Haskell looks
promising, it seems to be in the pre-beta stage. 

- Although the documentation is very good, it is rather bulky, which can
scare away newbies. 

- As Haskell is currently used a lot by people with an average IQ of 160,
the available packages and programming approaches are not easily absorbed
for the average software engineer with an IQ of 120 ;-) However, once you
take your time to dig deep into the matter, one often sees the beauty behind
it. But many newbies just feel really stupid when they look at Haskell code
:) I certainly did and still do, but fortunately I know I'm not very clever,
so that's okay ;)

- I haven't looked at the debuggers, but I've heared Haskell is really hard
to debug. 

Anyway, although my IQ is far below 160, I find Haskell the most exciting
language I have ever learned (and I've only scratched the bare surface of
the language)

Cheers,
Peter Verswyvelen


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


Re: [Haskell-cafe] Re: Parsec is being weird at me

2007-08-25 Thread Stefan O'Rear
On Sat, Aug 25, 2007 at 08:18:29PM +0100, Andrew Coppin wrote:
 But hang on a minute...

 many parses 0 or more occurrances of an item.

 sepBy parses 0 or more occurrances of an item, seperated by another item.

 endBy parses 0 or more occurrances of an item, terminated by another 
 item.

 sepEndBy parses 0 or more occurrances of an item, seperated *and* 
 terminated by another item.

 ...except that endBy doesn't seem to be working right. :-S

There is one other little bit of documented behavior.  Parsec's normal
combinators only parse LL(1) grammars.  Consult any work on formal
languages for the exact meaning and all the consequences, however for
this example it serves to note that after seeing abc, the single
character of lookahead '#' is not sufficient to determine the correct
parse.

Stefan


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


Re: [Haskell-cafe] Ideas

2007-08-25 Thread Andrew Coppin

Peter Verswyvelen wrote:

I tried vital, and at first sight it is very nice, but they only support a
very limited subset of Haskell, perform no type checking at all, don't
support the indent rule, etc... Anyway it is an amazing piece of work.

Regarding your question about visual programming, GEM Cutter from the Open
Quark Framework is also nice. http://labs.businessobjects.com/cal. But they
also wrote their own Haskell98 (with some Hugs extension) compiler in...
Java.

Cheers,
Peter Verswyvelen
  


Vital seems to have a really damn nice concept behind it. The visuals 
don't look quite so hot though... ;-)


If I could figure out how to do the whole drag boxes around, draw 
lines stuff with Gtk2hs, I might have a go at bettering this myself... 
but that's unlikely.


GEM Cutter also falls into the category of hey, that's interesting, I 
should go find out about this stuff... ;-)


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


Re: [Haskell-cafe] Ideas

2007-08-25 Thread Evan Laforge
 Reaktor has a few limitations though.

 1. It's virtually impossible to debug the thing! (I.e., if your synth
 doesn't work... good luck working out why.)

 2. It lacks looping capabilities. For example, you cannot build a
 variable-size convolution block - only a fixed-size one. (If you want to
 draw *a lot* of wires!) If you look through the standard library, you'll
 find no end of instruments that use a hack of using voice polyphony to
 crudely simulate looping... but it's not too hot.

 Would be nice if I could build something in Haskell that overcomes
 these. OTOH, does Haskell have any way to talk to the audio hardware?

Nyquist is a music language from a whlie back that I liked (in theory,
not so much in practice).  It has a functional model in that
instruments are just functions that return sample streams, so
there's no difference between signal processing and signal generating
functions (or orchestra and score, for the csounders out there).  This
was made efficient by lazily evaluating the streams and some custom
hackery where it would e.g. notice that one signal going into (+) had
ended and simply unlink the entire operation from the call graph, and
some gc hackery to reclaim sound blocks quickly.

The other interesting feature was behaviours which were just
dynamically scoped variables that would propagate down to the nearest
function that cared to interpret them, e.g. (transpose 5 (seq (melody
1) (melody 2))) would transpose the tones generated by (melody) by
setting a dynamic variable that would later be read by the underlying
oscillators or whatever that melody used.  seq used the mechanism to
shift or scale the beginnings end endings of notes.

It was also more powerful than e.g. csound, supecollider, or reaktor
style languages because in the former you have to compile a static
call graph (the orchestra) and then play it with signals
dynamically (the score), whereas in nyquist there's no orchestra and
score division.  The disadvantage is that the immutable signals made
it hard to implement real-time synthesis.

The practical problem was that it was implemented in a hacked up XLisp
which was primitive and hard to debug.  Added to that, you had to be
careful to wrap signals in functions or macros so the eager
interpreter wouldn't evaluate the whole signal and kill performance.

To get this back to haskell, at the time I wondered if a more natural
implementation might be possible in haskell, seeing as it was more
naturally lazy.  Not sure how to implement the behaviours though
(which were simply macros around a let of *dynamic-something*).  I'm
sure people have done plenty of signal processing, and there's always
haskore... but what about a sound generation language like csound or
clm or nyquist?  It could fit in nicely below haskore.



Also, as another reaktor user I agree it would have been so much nicer
were it simply a real language.  Drawing those boxes and lines and the
complete lack of abstraction (beyond copy and paste) is a real pain.
Supercollider is more promising in that way, but less polished of
course.  It also has that two-level imperative model though where you
create and modify your signal graph with imperative techniques, then
run it, rather than your program *being* the signal graph.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Ideas

2007-08-25 Thread Andrew Coppin

Evan Laforge wrote:

To get this back to haskell, at the time I wondered if a more natural
implementation might be possible in haskell, seeing as it was more
naturally lazy.  Not sure how to implement the behaviours though
(which were simply macros around a let of *dynamic-something*).  I'm
sure people have done plenty of signal processing, and there's always
haskore... but what about a sound generation language like csound or
clm or nyquist?  It could fit in nicely below haskore.
  


Indeed, you can write certain DSP algorithms beautifully in Haskell. 
Now, if only it could talk to the audio hardware... (Or just use common 
file formats even.)



Also, as another reaktor user I agree it would have been so much nicer
were it simply a real language.  Drawing those boxes and lines and the
complete lack of abstraction (beyond copy and paste) is a real pain.
Supercollider is more promising in that way, but less polished of
course.  It also has that two-level imperative model though where you
create and modify your signal graph with imperative techniques, then
run it, rather than your program *being* the signal graph.
  


Reaktor has abstraction. You can build a gizmo that does something 
useful, call it a macro, and then use it whereever you want.


If you want to build a gizmo that takes a siganl x and computes 
8*x*x*x - 8*x*x + 1 (i.e., the 4th Chebyshev polynomial), you've going 
to have to draw *a lot* of wires! It would be nice if there was some 
feature for quickly building complicated chunks of pure algebra like that.


It would also be nice if there were some way to *programmatically* 
construct the graph... but never mind. (Maybe in Reaktor 6?)


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


Re: [Haskell-cafe] Re: Parsec is being weird at me

2007-08-25 Thread Andrew Coppin

Stefan O'Rear wrote:

On Sat, Aug 25, 2007 at 08:18:29PM +0100, Andrew Coppin wrote:
  

But hang on a minute...

many parses 0 or more occurrances of an item.

sepBy parses 0 or more occurrances of an item, seperated by another item.

endBy parses 0 or more occurrances of an item, terminated by another 
item.


sepEndBy parses 0 or more occurrances of an item, seperated *and* 
terminated by another item.


...except that endBy doesn't seem to be working right. :-S



There is one other little bit of documented behavior.  Parsec's normal
combinators only parse LL(1) grammars.  Consult any work on formal
languages for the exact meaning and all the consequences, however for
this example it serves to note that after seeing abc, the single
character of lookahead '#' is not sufficient to determine the correct
parse.
  


Heh. Starting to wish I had a significantly higher IQ...

I thought the whole *purpose* of the endBy combinator was to keep 
applying one parser until the other one succeeds?


In the example I posted, the two parsers are quite trivial. But in the 
real problem I actually want to solve, they are very non-trivial...


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


Re: [Haskell-cafe] Ideas

2007-08-25 Thread Evan Laforge
 Indeed, you can write certain DSP algorithms beautifully in Haskell.
 Now, if only it could talk to the audio hardware... (Or just use common
 file formats even.)

Oh, that's easy.  I wrote an FFI interface to portaudio a while back
to write a delay-looping type utility in haskell.  It was pretty
trivial.  You could do the same for libsndfile or whatever.

The only thing I'm uncertain about is whether it would have good
enough time and space performance.  All the real work is writing yet
another set of basic envelope, oscillator, and fft primitives.  You
*should* be able to go all the way down to the samples in pure haskell
though, which would be more elegant than those other languages :)

 Reaktor has abstraction. You can build a gizmo that does something
 useful, call it a macro, and then use it whereever you want.

Well, except that if you then change your macro you have re-copy it
into every instrument or ensemble or other macro that uses it.  So I
consider the macros basically a copy and paste mechanism.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Ideas

2007-08-25 Thread C.M.Brown
 I tried vital, and at first sight it is very nice, but they only support a
 very limited subset of Haskell, perform no type checking at all, don't
 support the indent rule, etc... Anyway it is an amazing piece of work.

I believe that type-sensitive manipulation was certainly being
investigated; however, I can't confirm as to how far it *was*
investigated.

What intriged me mostly was how it can display infinite data structures
lazily. I think it's certainly a great tool for teaching some aspects of
functional programming: helping newbies to understand and define data
structures, say.

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


RE: [Haskell-cafe] Ideas

2007-08-25 Thread C.M.Brown
 Definitely! It's really cool stuff. But something like that for real Haskell
 (e.g. GHC) would be even better :) I could be an offline downloadable
 application. It would be a very nice tool: create postscript (or PDF, or
 LaTex, whatever rich text format) documents with Haskell boxes inside.
 Real literate programming... Oh well ;)

I would personally say Haskell 98 is real Haskell (well, until Haskell
Prime comes out). It becomes difficult for tool developers to cater for
non-standard languages; Haskell is quite complicated enough without having to 
cater
for all the little nuances and idiomatic extensions that are constantly
added with each release of a compiler.

I believe it does work as an offline downloadable tool...

http://www.cs.kent.ac.uk/projects/vital/install/index.html

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


[Haskell-cafe] Haskell on the Playstation 3? :-)

2007-08-25 Thread Peter Verswyvelen
Game developers are really struggling to get performance out of the
Playstation 3 console. This console has a single PowerPC CPU with 6 Cell SPU
coprocessors, all running at 3.3GHz. These SPUs have 256KB very high speed
local RAM, and data from the 512MB main memory can stream in and out via DMA
into these SPUs. The problem is that with imperative approaches this is a
nightmare to manage..

 

It would be a very cool project to show that Haskell could run on such a
platform, making it easier to take advance of its awesome power J

 

Oh well, I'm just brainstorming here.

 

Cheers,

Peter

 

BTW: This Cell platform also seemed to be offered for scientific computing
in standard workstation PCs, so it would not just be for the Playstation 3.

 

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


Re: [Haskell-cafe] Haskell on the Playstation 3? :-)

2007-08-25 Thread Radosław Grzanka
 It would be a very cool project to show that Haskell could run on such a
 platform, making it easier to take advance of its awesome power J

It's funny. But 5 minutes ago I was thinking: did anyone compiled
haskell application for Palm (m68k and/or Arm) that runs on Palm OS? I
can literally quote you: It would be a very cool project to show that
Haskell could run on such a platform. Ofcourse this is completly
other way around in terms of power and memory. :)

But anyway, did anyone do it?

Cheers,
  Radek.

-- 
Codeside: http://codeside.org/
Przedszkole Miejskie nr 86 w Lodzi: http://www.pm86.pl/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Text.Xhtml.Strict

2007-08-25 Thread Marco Túlio Gontijo e Silva
Hello there.

I don't know if it's off topic, but I don't know where else to ask.

I've been using Text.Xhtml.Strict, and I'm wondering why the functions
are mostly Html - Html and not HTML a = a - Html, or something
similar.  If they were like this,  and toHtml would be not needed,
what would make it simpler to call the functions with arguments that
are not Html.

The question is specific to this library, but I think it's a very
general one: isn't it better to have more generic functions with type
changing inside?  It seems to me that it would make things better from
the users point of view. What do you think?

-- 
Marco Túlio Gontijo e Silva
Blog: http://marcotmarcot.blogspot.com/
Página: http://marcotmarcot.googlepages.com/
Correio, Jabber, GTalk, MSN: [EMAIL PROTECTED]
IRC: [EMAIL PROTECTED]
IRC: [EMAIL PROTECTED]
Skype: marcotmarcot
Telefone: 33346720
Celular: 98116720
Endereço:
  Rua Paula Cândido, 257/201
  Gutierrez 30430-260
  Belo Horizonte/MG Brasil
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] :, infix operator, infix constructor, et cetera

2007-08-25 Thread Daniel C. Bastos
There is something called infix constructors and something else called
infix operators. I'm guessing that an infix operator is really a
function, and an infix constructor I don't know what it is. How would
you guys describe them?

(*) More questions.

I learned how to define (++), and then I wanted to see how (:) would be
defined. The Haskell 98 Report mentions that

-- The (:) operator is built-in syntax, and cannot legally be given
-- a fixity declaration; but its fixity is given by:
--   infixr 5  :

What does ``built-in syntax'' mean? 

Paul Hudak, in ``The Haskell School of Expression'' mentions that he
defines (:) legally, in Appendix A. After writing 

data [a] = [] | a : [a]  -- more pseudo-code
infixr 5 :

and making a couple of observations about it, he writes:

``The way (:) is defined here is actually legal syntax. Infix
constructors are permitted in *data* declarations, and are distinguished
from infix operators (for pattern-matching purposes) by the fact that
they must begin with a colon (a property trivially satisfied by :).''

So I'm not sure what ``legal syntax'' and ``pseudo-code'' exactly
mean. The program

 module Main where 

 data [a] = [] | a : [a]
 infixr 5 :

 main = putStrLn hello world

gives

%runhugs.exe Colon.lhs 
runhugs: Error occurred
ERROR Colon.lhs:3 - Syntax error in data declaration (unexpected `[')

(*) The 5.

What does that 5 do in ``infixr 5 :''?

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


Re: [Haskell-cafe] Haskell on the Playstation 3? :-)

2007-08-25 Thread Jeremy Shaw
At Sun, 26 Aug 2007 00:19:25 +0200,
=?UTF-8?Q?Rados=C5=82aw_Grzanka?= wrote:

 It's funny. But 5 minutes ago I was thinking: did anyone compiled
 haskell application for Palm (m68k and/or Arm) that runs on Palm OS?

I have looked into doing this in the past. Historically speaking, the
first obstacle is all the Haskell compilers I looked at required
libgmp -- which I could not get to compile for PalmOS. libgmp was used
primarily (entirely?) for supporting the Integer data type.

I believe there is now one (or more?) pure Haskell implementations of
Integer -- so, it should be easier to remove the libgmp dependency. 

I also heard wild rumors that a future version of GHC might have
backend that generates pure ANSI C. In theory, that should make it
much easier to target PalmOS.

I have never written anything for PalmOS, aside from some scheme
programs using LispMe, but I think it might be a pretty unusual
platform. For example, it seems like applications can not access for
than 4k of ram without some hackery.

Another option would be to port the yhi bytecode interpreter to run on
PalmOS. I tried this, but I ran into three problems:

 1. libgmp dependency
 2. build system requires Python (scons).
 3. I 'upgraded' to a Nokia 770, and suddenly did not care about PalmOS

There is also an old project to port nhc98 to PalmOS -- not sure if it
is still active, or how far they got. AFAIK, nothing was ever
released.

If PalmOS is really un-POSIX compatible, it may be easier to write a
custom compiler that compiles YHC or GHC Core to PalmOS. Well, the
first time you try to write a compiler from Core - ??? is
difficult, but the second time around is a lot easier ;)

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


Re: [Haskell-cafe] Haskell on the Playstation 3? :-)

2007-08-25 Thread Neil Mitchell
Hi

 Another option would be to port the yhi bytecode interpreter to run on
 PalmOS. I tried this, but I ran into three problems:

  1. libgmp dependency

This is no longer an issue, we now have a flag to not require libgmp,
which makes type Integer = Int

  2. build system requires Python (scons).

Still alas, but we'd like to fix it.


 If PalmOS is really un-POSIX compatible, it may be easier to write a
 custom compiler that compiles YHC or GHC Core to PalmOS. Well, the
 first time you try to write a compiler from Core - ??? is
 difficult, but the second time around is a lot easier ;)

We have compilers from Yhc Core to everything nowadays. One to Lisp
shouldn't be too tricky, if someone wanted to take that direction.

Thanks

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


Re: [Haskell-cafe] Ideas

2007-08-25 Thread Derek Elkins
On Sat, 2007-08-25 at 22:51 +0100, Philippa Cowderoy wrote:
 On Sat, 25 Aug 2007, Andrew Coppin wrote:
 
  Would be nice if I could build something in Haskell that overcomes these.
  OTOH, does Haskell have any way to talk to the audio hardware?
  
 
 It would definitely be nice if someone wrote a binding to the VST SDK or a 
 wrapper for it. Unfortunately I suspect it's too windows-specific for most 
 of those on the list, and there isn't a sufficiently good portable and 
 widely-used/available alternative. 
 

I recently wrote a binding to LADSPA.  I just need to finish packaging
it and upload it to Hackage.

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


Re: [Haskell-cafe] Ideas

2007-08-25 Thread Derek Elkins
On Sat, 2007-08-25 at 23:36 +0200, [EMAIL PROTECTED]
wrote:
 Evan Laforge writes: 
 
  Indeed, you can write certain DSP algorithms beautifully in Haskell.
  Now, if only it could talk to the audio hardware... (Or just use common
  file formats even.)
  
  Oh, that's easy.  I wrote an FFI interface to portaudio a while back
  to write a delay-looping type utility in haskell.  It was pretty
  trivial.  You could do the same for libsndfile or whatever. 
  
  The only thing I'm uncertain about is whether it would have good
  enough time and space performance.  All the real work is writing yet
  another set of basic envelope, oscillator, and fft primitives.  You
  *should* be able to go all the way down to the samples in pure haskell
  though, which would be more elegant than those other languages :)
 
 == 
 
 Well, if you want to see what you can do with a lazy functional language,
 not necessarily Haskell, but Clean (sorry for advertizing a competitor
 on this list...), perhaps have a look on my PADL paper 
 
 http://users.info.unicaen.fr/~karczma/arpap/cleasyn.pdf 
 
 I generated .wav files as output, from lazy streams, so the sound was 
 off-line.
 My ambition was to code in a very, very compact way some musical
 instruments, with looping replaced by co-recursion. It cannot be extremely
 efficient, but it seems quite elegant and powerful. 

Last week I did exactly that.  Using lazy streams and a quickly hacked
up .wav file output, I played with some of the extended Karplus-Strong
plucked string/drum synthesis algorithms.

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


[Haskell-cafe] GHC from source makes a great hardware test

2007-08-25 Thread Dave Bayer

I recently did the classic push a shopping cart down the aisle at
Fry's to build a Core 2 Quad computer, with Linux swap and a soft
raid array spread across three 750 GB sata hard disks. I had some
potential first build issues, notably a mishap with the lawn of
copper grass that passes for a 775 cpu socket, followed by an hour of
brain-surgery with a magnifying glass and a tiny screwdriver. I was
very curious to test the stability of this system when it booted up
after all; the best hardware test I could think of was multiple
processes building GHC from source, with each iteration using the
previous GHC binary as the compiler for the new build.

Four iterating GHC builds in parallel is enough to peg all four cores
at 100% indefinitely, with considerable disk activity to the soft raid
array. The most I had going at once was 30 GHC builds; the system
remained responsive enough for me to gracefully change my mind in the
morning.

Building multiple copies of GHC generates a lot of heat; going full
tilt, the computer was drawing 220 watts at the wall. I don't use air
conditioning for my summer office, so I ended up taping a small
bathroom exhaust fan and dimmer switch into the back of a cardboard
box, to collect the hot air from the back of the computer and send it
out the window through a dryer hose. This kept the cores at 40 C (the
enclosure itself has all possible fans) and my office cooler. A
previous passive dryer hose arrangement kept the computer at 50 C,
which is cooler than my MacBook cpu at full tilt, but I like to build
things. Cardboard is an awesome quick prototyping material.

Someone else in the same boat might save some time by modifying my
Bash script. I ran hundreds of GHC builds without a mishap, and
concluded that my system is stable.

 #!/bin/bash

 # ghc-test.sh

 # Bash script to iteratively build ghc from source
 # http://www.haskell.org/ghc

 # usage:
 #   ghc-test iters [ghc]

 # Bash scripting reference: Advanced Bash-Scripting Guide
 # http://tldp.org/LDP/abs/html/index.html

 # Customize these parameters to local installation:

 sourcedir=/home/me/ghc-6.6.1
 src1=${sourcedir}/ghc-6.6.1-src.tar.bz2
 src2=${sourcedir}/ghc-6.6.1-src-extralibs.tar.bz2

 testdir=/media/raid/ghc-test
 log=${testdir}/log.txt
 ghcdir=ghc-6.6.1
 binarypath=driver/ghc/ghc


 # determine build directory
 time=$(date +'%Y%m%d-%H%M%S')
 builddir=${testdir}/${time}


 # determine number of iterations
 if [[ -z $1 ]]
 then
 iters=2
 else
 iters=$1
 fi


 # choose ghc binary to use
 if [[ -n $2  -f $2  -x $2 ]]
 then
 ghc=$2
 else
 ghc=$(which ghc)
 fi


 # check ghc binary for pulse
 fib=`${ghc} -e 'let x = 0 : 1 : zipWith (+) x (tail x) in x !! 99'`
 if [[ ${fib} != 218922995834555169026 ]]
 then
 echo ** bad ** ${ghc} ${iters} ${time}  ${log}
 ghc=$(which ghc)
 else
 echo ok${ghc} ${iters} ${time}  ${log}
 fi


 # do an iteration if $iters  0
 let iters=iters-1
 if [[ ${iters} -gt 0 ]]
 then

 # build new copy of ghc from source
 mkdir -p ${builddir}
 cd ${builddir}
 tar -jxf ${src1}
 tar -jxf ${src2}
 cd ${ghcdir}
 ./configure --with-ghc=${ghc}
 make

 # delete previous build directory, now that we're done with $ghc
 if [[ -n $3  -d $3 ]]
 then
 rm -rf $3
 fi

 # iterate
 newghc=${builddir}/${ghcdir}/${binarypath}
 ${sourcedir}/ghc-test.sh ${iters} ${newghc} ${builddir}

 else

 # delete previous build directory
 if [[ -n $3  -d $3 ]]
 then
 rm -rf $3
 fi

 fi

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


Re: [Haskell-cafe] GHC from source makes a great hardware test

2007-08-25 Thread Stefan O'Rear
On Sat, Aug 25, 2007 at 09:33:25PM -0700, Dave Bayer wrote:
 I recently did the classic push a shopping cart down the aisle at
 Fry's to build a Core 2 Quad computer, with Linux swap and a soft
 raid array spread across three 750 GB sata hard disks. I had some
 potential first build issues, notably a mishap with the lawn of
 copper grass that passes for a 775 cpu socket, followed by an hour of
 brain-surgery with a magnifying glass and a tiny screwdriver. I was
 very curious to test the stability of this system when it booted up
 after all; the best hardware test I could think of was multiple
 processes building GHC from source, with each iteration using the
 previous GHC binary as the compiler for the new build.

You might also try running the Jhc library build; on my system, that
gets the processor about 5C hotter than a GHC build.

Stefan


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