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 data-structure. (This may be
| tricky, but I think I know how to do it).

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).

If it doesn't, someone would have to add the Python calling convention
to the various implementations.   

Simon


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



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 main() routine,
though? Is that true? And if, why is that necessary?

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



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 of fields in your record.

 Right now I'm using a record of STRefs, like:
 data E s = E{
   refi ::  STRef s Int,
   refc ::  STRef s Char
 }
 
 but it can get a little messy, since thread s propagates to 
 every datatype that uses the record type in it's definition.

Here's another trick if you use this route:

 data E s = E{
   refi ::  !STRef s Int,
   refc ::  !STRef s Char
 }

and compile with -funbox-strict-fields.  This will eliminate the boxing
of the STRefs.

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



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 = untilEOF (getChar=putChar)

catchEOF io = catch io (\e-unless (IO.isEOFError e) (ioError e))
untilEOF io = catchEOF (sequence_ $ repeat io) 

main = main2
\end{code}

Claus

PS. I haven't kept up to date with buffering issues,
and hugs/ghci may not like this kind of code..
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



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 text, and maybe processes a bit.
 | c) Returns the parsed data-structure. (This may be
 | tricky, but I think I know how to do it).
 
 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).
 
 If it doesn't, someone would have to add the Python
 calling convention
 to the various implementations.   

Unfortunately, Python does not support calling
arbitrary C functions. In order to call C functions
from Python, you have to write a “Python extension
module”. (This restriction is actually a direct result
of Python being interpreted, rather than compiled.)

But I do have another idea: If I was working only on
Windows, I could have used HaskellDirect to wrap the
Haskell code as a COM component, and since Python
seems to have good COM support (though I never used
it) this would have solved my problem neatly.

However, I need Linux portability, which rules out
using COM. But there is a good COM alternative for
Linux: XPCOM from the Mozilla project. This is a
cross-platform and somewhat improved COM, which has
C++, Java, JavaScript, Perl, and Python bindings. And
this brings me to my next question: How difficult
would it be to extend HaskellDirect to support XPCOM?

Thanks,
  -JH


__
Do you Yahoo!?
U2 on LAUNCH - Exclusive greatest hits videos
http://launch.yahoo.com/u2
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



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
| Update Integer
| GAdd | GSub | GMul | GDiv | GMod | GPow
| GNeg | GAbs
deriving (Eq, Ord, Read, Show)

type Tmp = Integer

data ROp
= LoadImm Tmp Integer
| RAdd Tmp Tmp Tmp
| RSub Tmp Tmp Tmp
| RMul Tmp Tmp Tmp
| RDiv Tmp Tmp Tmp
| RMod Tmp Tmp Tmp
| RPow Tmp Tmp Tmp
| RNeg Tmp Tmp
| RAbs Tmp Tmp
deriving (Eq, Ord, Read, Show)

type CounterT m t = StateT Integer m t
type StackT t = State [Integer] t

type GST t = RWS () [ROp] (Integer, [Integer]) t

class Stack f where
pushVal, push, pop, update, slide :: Integral t = t - f ()
popVal :: Integral t = f t

instance Integral t = Stack (RWS () [ROp] (t, [t])) where
pushVal n = do
(ctr, stk) - get
put (ctr, fromIntegral n : stk)
popVal = do
(ctr, top:stk) - get
put (ctr, stk)
return (fromIntegral top)
push n = do
(ctr, stk) - get
put (ctr, stk!!fromIntegral n : stk)
pop n = do
(ctr, stk) - get
put (ctr, drop (fromIntegral n) stk)
slide n = do
(ctr, top:stk) - get
put (ctr, top : drop (fromIntegral n) stk)
update n = do
(ctr, top:stk) - get
let (front, _:back) = splitAt (fromIntegral n) stk
put (ctr, front ++ [top] ++ back)

class Counter f where
gen :: Enum t = f t

instance Integral t = Counter (RWS () [ROp] (t, [t])) where
gen = do
(ctr, stk) - get
put (ctr + 1, stk)
return . toEnum . fromIntegral $ ctr + 1

instance (Enum t, Monad m) = Counter (StateT t m) where
gen = do
ctr - get
put $ succ ctr
ctr - get
return . toEnum $ fromEnum ctr

translate gOps = snd $ evalRWS (mapM trans gOps) () (0,[])

trans :: GOp - GST ()
trans i = case i of
PushVal n   -
do
reg - gen
tell [LoadImm reg n]
pushVal reg
Push n  - push n
Pop n   - pop n
Slide n - slide n
Update n- update n
GAdd- doBinOp RAdd
GSub- doBinOp RSub
GMul- doBinOp RMul
GDiv- doBinOp RDiv
GMod- doBinOp RMod
GPow- doBinOp RPow
GNeg- doUnOp RNeg
GAbs- doUnOp RAbs
where
doUnOp op =
do
x - popVal
y - gen
tell [op y x]
pushVal y
doBinOp op =
do
x - popVal
y - popVal
z - gen
tell [op z x y]
pushVal z
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



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 PROTECTED]
  than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume

On Wed, 13 Nov 2002, William Lee Irwin III wrote:

 On Wed, Nov 13, 2002 at 03:29:53PM +0900, Ahn Ki-yung wrote:
  If you are steaming with compicated codes, then how about taking a break.
  Let's play with a simple cat.
  \begin{code}
  main = mapM (=putChar) getCharS where getCharS = getChar:getCharS
  \end{code}
 
 Why not this?
 
 main = mapM_ (\h - mapM_ putChar = hGetContents h) = mapM (flip openFile $ 
ReadMode) = getArgs
 
 
 Bill
 ___
 Haskell-Cafe mailing list
 [EMAIL PROTECTED]
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 

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



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 number of fields in your record.
One of them has 4, the other 3, but they might grow bigger...


 Here's another trick if you use this route:
added some parenthesis
  data E s = E{
refi ::  !(STRef s Int),
refc ::  !(STRef s Char)
  }

 and compile with -funbox-strict-fields.  This will eliminate the boxing
 of the STRefs.

Nice, thanks :)


One more question. 
I'm passing that 'record' around as an implicit value. The record as STRefs 
that I use to collect info, but it also has some pure fields with 'read-only' 
info. Something like,

data E s = E{
  refi :: STRef s Int,
  refc :: STRef s Char,
  max  :: Int
}

In some functions I might need only some pure fields, and none of the STRefs, 
but since I pass something of type 'E s' around, everything ends up beeing 
monadic. Is using two records (on with STRefs and one with pure fields) the 
only/best way to avoid this? 
I would like to use two records, doesn't seem natural, but I also don't like 
to end up using monadic functions when they are, in fact, pure...

Thanks,
J.A.




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



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 above takes
files from the command-line, though it does fail to accommodate the
pass-through case, which is handled by:

main = getArgs = \args -if args == [] then interact id else mapM readFile args = 
mapM_ putStr

.. which seems to be a bit above 80 chars. Some library function trickery
is probably in order to cut the if statement down to size. e.g.

nonEmptyMapM_ :: Monad m = m () - (t - m ()) - [t] - m ()
nonEmptyMapM_ def _ []   = def
nonEmptyMapM_ _   f xs@(_:_) = mapM_ f xs
main = getArgs = nonEmptyMapM_ (interact id) ((= putStr) . readFile)

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