RE: Calling Haskell from Python / C++

2002-11-13 Thread Simon Peyton-Jones
| So here is what I envision: I write the main | application in Python. I write a (hopefully) small | Haskell module that: | a) Calls back to the main Python app for reading the | text to be parsed, preferably using laziness. | b) Parses the text, and maybe processes a bit. | c) Returns the parsed

Re: Calling Haskell from Python / C++

2002-11-13 Thread Peter Simons
Simon Peyton-Jones writes: If Python uses C's calling convention, it might be easy; just use 'foreign import' and 'foreign export' (see the FFI spec at haskell.org). I remember reading that the main program, that wants to call Haskell code, would have to be compiled with a special Haskell

RE: Record of STRefs better than STRef to a Record?

2002-11-13 Thread Simon Marlow
If I use an STRef to a record, will a new record be created each time I want to update a single field? Or can I expect GHC to optimize it and have the field of the record updated in place? You'll get a new record for each update. This might not be so bad though, depending on the number

Re: 1 line simple cat in Haskell

2002-11-13 Thread C.Reinke
main = mapM (=putChar) getCharS where getCharS = getChar:getCharS How would you suggest to neatly insert the error handling code into ? \begin{code} -- some suggestions for a little zoo of cats module Main where import IO import Monad main0 = interact id main1 = getContents = putStr main2 =

RE: Calling Haskell from Python / C++

2002-11-13 Thread Jonathan Holt
--- Simon Peyton-Jones [EMAIL PROTECTED] wrote: | So here is what I envision: I write the main | application in Python. I write a (hopefully) small | Haskell module that: | a) Calls back to the main Python app for reading the | text to be parsed, preferably using laziness. | b) Parses the

monadic stack to register machine translator

2002-11-13 Thread William Lee Irwin III
module GT where import Monad import Monoid import MonadState import MonadWriter import MonadRWS -- Just a quick exercise in using monads. -- Thought it'd be nice to share with the class. data GOp = PushVal Integer | Push Integer | Pop Integer | Slide Integer

Re: 1 line simple cat in Haskell

2002-11-13 Thread Hal Daume III
I'm not sure why someone hasn't suggested main = interact id which I think would accomplis everything you want, and probably be a heck of a lot faster, as (apparently) putChar and getChar are quire inefficient. -- Hal Daume III Computer science is no more about computers| [EMAIL

Re: Record of STRefs better than STRef to a Record?

2002-11-13 Thread Jorge Adriano
If I use an STRef to a record, will a new record be created each time I want to update a single field? Or can I expect GHC to optimize it and have the field of the record updated in place? You'll get a new record for each update. This might not be so bad though, depending on the

Re: 1 line simple cat in Haskell

2002-11-13 Thread William Lee Irwin III
On Wed, 13 Nov 2002, William Lee Irwin III wrote: main = mapM_ (\h - mapM_ putChar = hGetContents h) = mapM (flip openFile $ ReadMode) = getArgs On Wed, Nov 13, 2002 at 07:46:41AM -0800, Hal Daume III wrote: main = interact id There is a semantic difference here, as the version I posted