Re: [Haskell-cafe] Re: Bound threads

2005-03-01 Thread Marcin 'Qrczak' Kowalczyk
Marcin 'Qrczak' Kowalczyk [EMAIL PROTECTED] writes:

 Why is the main thread bound?

I can answer myself: if the main thread is unbound, the end of the
program can be reached in a different OS thread, which may be a
problem if we want to return cleanly to the calling code.

I've now implemented a threaded runtime in my language Kogut, based
on the design of Haskell. The main thread is bound. The thread which
holds the capability performs I/O multiplexing itself, without a
separate service thread.

Producer/consumer ping-pong is 15 times slower between threads running
on different OS threads than on two unbound threads.

-- 
   __( Marcin Kowalczyk
   \__/   [EMAIL PROTECTED]
^^ http://qrnik.knm.org.pl/~qrczak/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Bound threads

2005-03-01 Thread Benjamin Franksen
On Tuesday 01 March 2005 12:20, Marcin 'Qrczak' Kowalczyk wrote:
 Marcin 'Qrczak' Kowalczyk [EMAIL PROTECTED] writes:
  Why is the main thread bound?

 I can answer myself: if the main thread is unbound, the end of the
 program can be reached in a different OS thread, which may be a
 problem if we want to return cleanly to the calling code.

 I've now implemented a threaded runtime in my language Kogut, based
 on the design of Haskell. The main thread is bound. The thread which
 holds the capability performs I/O multiplexing itself, without a
 separate service thread.

 Producer/consumer ping-pong is 15 times slower between threads
 running on different OS threads than on two unbound threads.

Which OS?

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


Re: [Haskell-cafe] Browser-like UI

2005-03-01 Thread Duncan Coutts
In message [EMAIL PROTECTED] =?ISO-8859-1?Q?Maur=EDcio?=
[EMAIL PROTECTED] writes:
Hi,
 
I've seen some options for GUI programming in Haskell libraries page, 
 but what I really would like is to define my user interface using HTML 
 (or, maybe, SVG). What are the options to do that in Haskell? I've read 
 that Gtk2Hs has a mozilla rendering engine, but unfortunatly that won't 
 build on my 64Mb computer. What else can I use? How does that work, can 
 I handle HTML events with Haskell code?

If there are no pre-built packages of gtk2hs for your system you can still build
from source in a reasonably straigtforward way. Basically we provide pre-built
versions of the problematic files that take so much memory to create in an
ordinary build. The remainer of the build does not require very much memory.

See this FAQ:
http://gtk2hs.sourceforge.net/archives/2005/02/18/building-on-machines-with-less-ram/

If there are no versions of these pre-built files that are appropriate for your
platform please ask on the gtk2hs mailing list and we'll see what we can do.

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


[Haskell-cafe] Re: Browser-like UI

2005-03-01 Thread Maurício

  I've seen some options for GUI programming in Haskell libraries page, 
but what I really would like is to define my user interface using HTML 
(or, maybe, SVG). What are the options to do that in Haskell? I've read 
that Gtk2Hs has a mozilla rendering engine, but unfortunatly that won't 
build on my 64Mb computer. What else can I use? How does that work, can 
I handle HTML events with Haskell code?

If there are no pre-built packages of gtk2hs for your system you can still build
from source in a reasonably straigtforward way. Basically we provide pre-built
versions of the problematic files that take so much memory to create in an
ordinary build. The remainer of the build does not require very much memory.
See this FAQ:
http://gtk2hs.sourceforge.net/archives/2005/02/18/building-on-machines-with-less-ram/
If there are no versions of these pre-built files that are appropriate for your
platform please ask on the gtk2hs mailing list and we'll see what we can do.
  I did read that FAQ, but it says that I should build with:
$ ./configure --disable-gnome --disable-mozilla
  Doesn't that means that the mozilla interface should be disabled?
  Maurício
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Numeric vs. relative precedences of infix operators

2005-03-01 Thread Henning Thielemann

On Mon, 28 Feb 2005 [EMAIL PROTECTED] wrote:

 G'day all.

 Quoting [EMAIL PROTECTED]:

  Widely accepted is a widely accepted relativism...
  I am also annoyed by the precedences 0,1,2, ...,9, etc.
 
  Why not 10, 20, 30,... ??

 I _think_ we had this back around Haskell 1.1 (which I never used, but
 early Gofers also had it).  Moreover, operators could also have arbitrary
 fixity (prefix, infix, postfix).

 I'm not sure why this feature was dropped,

Because of readability I don't plead for arbitrary fixities, I think the
current solution of infix operators in Haskell is enough. There is really
no advantage of n ! over faculty n.


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


Re: [Haskell-cafe] Re: Bound threads

2005-03-01 Thread Marcin 'Qrczak' Kowalczyk
Benjamin Franksen [EMAIL PROTECTED] writes:

 Producer/consumer ping-pong is 15 times slower between threads
 running on different OS threads than on two unbound threads.

 Which OS?

Linux/NPTL.

A context switch which changes OS threads involves:
   setitimer
   pthread_sigmask
   pthread_mutex_lock
   pthread_cond_signal
   pthread_cond_wait (starting)
and in the other thread:
   pthread_cond_wait (returning)
   pthread_mutex_unlock
   pthread_sigmask
   setitimer

setitimer is necessary because I tested that it is installed per
thread rather than per process, even though SUSv3 says it should be
per process.

pthread_sigmask makes the thread holding the capability handle signals.
I've heard that the interaction of signals and threads is broken in
pre-NPTL Linux threads, I will have to check how it behaves and what
should be used in this case (perhaps having signals unblocked in all
threads).

-- 
   __( Marcin Kowalczyk
   \__/   [EMAIL PROTECTED]
^^ http://qrnik.knm.org.pl/~qrczak/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Browser-like UI

2005-03-01 Thread Duncan Coutts
On Tue, 2005-03-01 at 11:15 -0300, Maurício wrote:
  If there are no pre-built packages of gtk2hs for your system you can still 
  build
  from source in a reasonably straigtforward way. Basically we provide 
  pre-built
  versions of the problematic files that take so much memory to create in an
  ordinary build. The remainer of the build does not require very much memory.
  
  See this FAQ:
  http://gtk2hs.sourceforge.net/archives/2005/02/18/building-on-machines-with-less-ram/
  
  If there are no versions of these pre-built files that are appropriate for 
  your
  platform please ask on the gtk2hs mailing list and we'll see what we can do.
  
 
I did read that FAQ, but it says that I should build with:
 
 $ ./configure --disable-gnome --disable-mozilla
 
Doesn't that means that the mozilla interface should be disabled?

I have added an additional overlay bundle for mozilla support and
updated the FAQ accordingly. This is somewhat experimental so if it
works or does not work it'd be useful for me to know.

Duncan

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


Re: [Haskell-cafe] Numeric vs. relative precedences of infix operators

2005-03-01 Thread Benjamin Franksen
On Tuesday 01 March 2005 15:28, Henning Thielemann wrote:
 On Mon, 28 Feb 2005 [EMAIL PROTECTED] wrote:
  G'day all.
 
  Quoting [EMAIL PROTECTED]:
   Widely accepted is a widely accepted relativism...
   I am also annoyed by the precedences 0,1,2, ...,9, etc.
  
   Why not 10, 20, 30,... ??
 
  I _think_ we had this back around Haskell 1.1 (which I never used, but
  early Gofers also had it).  Moreover, operators could also have arbitrary
  fixity (prefix, infix, postfix).
 
  I'm not sure why this feature was dropped,

 Because of readability I don't plead for arbitrary fixities, I think the
 current solution of infix operators in Haskell is enough. There is really
 no advantage of n ! over faculty n.

There is a good argument for 'distfix' i.e. bracketing operators, IMO. You 
could define your own if_then_else:

`if cond `then` truebranch `else` falsebranch end`

(Syntax, terminology, and example stolen from Macros and Preprocessing in 
Haskell, (1999) by Keith Wansbrough, see 
http://citeseer.ist.psu.edu/wansbrough99macros.html)

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


[Haskell-cafe] how do I avoid excessive constructor application?

2005-03-01 Thread S. Alexander Jacobson
For some reason, these two functions have different types.
  fun1 f (Left x)= Left (f x)
  fun1 _ r@(Right x) = Right x
  fun2 f (Left x) = Left (f x)
  fun2 _ r = r
Is there a way to rewrite fun2 so that f has type (a-b)?
In the general case, it seems wasteful to have to destruct and 
construct values just for type checking reasons, especially if your 
type has many more constructors than (Either a b).

-Alex-
__
S. Alexander Jacobson tel:917-770-6565 http://alexjacobson.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-Cafe] FFI and foreign function returning a structure

2005-03-01 Thread Dimitry Golubovsky
Hi,
If I have a C function returning a structure (not a pointer, but 
structure itself), can this be accomodated via FFI?

I re-read the FFI Addendum, and my conclusion is most likely No. I am 
asking just to make sure this is not only my finding.

Dimitry Golubovsky
Middletown, CT
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] how do I avoid excessive constructor application?

2005-03-01 Thread Ben Lippmeier
S. Alexander Jacobson wrote:
For some reason, these two functions have different types.
  fun1 f (Left x)= Left (f x)
  fun1 _ r@(Right x) = Right x
  fun2 f (Left x) = Left (f x)
  fun2 _ r = r
fun1 :: forall a a1 b . (a - a1) - Either a b - Either a1 b
fun2 :: forall a b. (a - a)  - Either a b - Either a  b
fun1 is indeed more general than fun2 because there is no way for an x 
inside a (Left x) from the LHS of the function to be returned as part of 
the result.

---
You can play games with the type checker to force them to have the same 
type without changing the meaning of your function.

fun1' f (Left x)= if True then Left (f x) else Left x
fun1' _ r@(Right x) = Right x
 :type fun1'
fun1' :: forall b a. (a - a) - Either a b - Either a b
This assumes that the compiler doesn't perform an optimisation that 
throws away the second alternative of the if statement before it does 
type checking.

---
A more sensible way is to add an explicit type signature to force it to 
have a less general type than what was inferred.

fun1 :: forall a b . (a - a) - Either a b - Either a b

Is there a way to rewrite fun2 so that f has type (a-b)?
Delete the second line, but then you have a different function.

In the general case, it seems wasteful to have to destruct and construct 
values just for type checking reasons, especially if your type has many 
more constructors than (Either a b).
Standard type inference always returns the *most general* type, and it 
is never wrong (unless there's a bug in the compiler).

If you actually want a less general type for one of your functions 
(maybe the more general one isn't useful in your particular program) 
then add a type signature to constrain it.

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


Re: [Haskell-Cafe] FFI and foreign function returning a structure

2005-03-01 Thread Ben Lippmeier
Dimitry Golubovsky wrote:
Hi,
If I have a C function returning a structure (not a pointer, but 
structure itself), can this be accomodated via FFI?
No. The way data is organised in memory is dramatically different in 
Haskell when compared with C. You need to write functions to read in 
each field in turn and then reconstruct the structure on the Haskell 
side.

It's a tedious process. My advice is that if you have a lot of 
structures to read, write a (simple) preprocessor to generate the 
marshalling code.. that's what I did.

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


Re: [Haskell-Cafe] FFI and foreign function returning a structure

2005-03-01 Thread shelarcy
I think this is relation to my problem.
(B
(BI wnant to write Haskell interface to FFmpeg. So first, I try to port
(Boutput_example.c to Haskell. But output_example.c's wants to initialize
(Bstructure like this,
(B
(B
(Bvoid write_audio_frame(AVFormatContext *oc, AVStream *st)
(B{
(B  int out_size;
(B  AVCodecContext *c;
(B  AVPacket pkt;
(B  av_init_packet(pkt);
(B
(B  c = st-codec;
(B
(B  get_audio_frame(samples, audio_input_frame_size, c-channels);
(B
(B  pkt.size= avcodec_encode_audio(c, audio_outbuf, audio_outbuf_size,
(Bsamples);
(B
(B  pkt.pts= c-coded_frame-pts;
(B  pkt.flags |= PKT_FLAG_KEY;
(B  pkt.stream_index= st-index;
(B  pkt.data= audio_outbuf;
(B
(B  /* write the compressed frame in the media file */
(B  if (av_write_frame(oc, pkt) != 0) {
(B  fprintf(stderr, "Error while writing audio frame\n");
(B  exit(1);
(B  }
(B}
(B
(Bthen I need to return a structure.
(B
(BBut I know that :
(B
(BOn Wed, 02 Mar 2005 14:45:54 +1100, Ben Lippmeier
(B[EMAIL PROTECTED] wrote:
(B No. The way data is organised in memory is dramatically different in  
(B Haskell when compared with C. You need to write functions to read in  
(B each field in turn and then "reconstruct" the structure on the Haskell  
(B side.
(B
(B It's a tedious process. My advice is that if you have a lot of  
(B structures to read, write a (simple) preprocessor to generate the  
(B marshalling code.. that's what I did.
(B
(B
(Bso I wrote a code like this,
(B(This use hsc2hs to write "read and write each field".)
(B
(B-
(B-- -*- mode: haskell -*-
(B{-# OPTIONS -fglasgow-exts #-}
(B
(B#include avformat.h
(B#include avcodec.h
(B
(Bmodule FFmpeg
(Bwhere
(B
(Bimport Foreign
(B
(Bdata CAVPacket = CAVPacket {pktPts :: !(#type int64_t), pktDts :: !(#type
(Bint64_t),
(B  pktDatas :: !(Ptr (#type uint8_t)), pktSize ::
(B!Int, pktStreamIndex :: !Int,
(B  pktFlags :: !Int, pktDuration :: !Int}
(B  deriving (Eq,Show)
(B
(Binstance Storable CAVPacket where
(Bpeek p   = do{ pts - (#peek AVPacket, pts) p; dts - (#peek AVPacket,
(Bdts) p;
(B   datas - (#peek AVPacket, data) p; size - (#peek
(BAVPacket, size) p;
(B   stream_index - (#peek AVPacket, stream_index) p; flags
(B- (#peek AVPacket, flags) p;
(B   duration - (#peek AVPacket, duration) p;
(B   return $! CAVPacket pts dts datas size stream_index flags
(Bduration }
(Bpoke p (CAVPacket pts dts datas size stream_index flags duration)
(B  = do{(#poke AVPacket, pts) p pts; (#poke AVPacket, dts) p dts;
(B   (#poke AVPacket, data) p datas; (#poke AVPacket, size) p
(Bsize;
(B   (#poke AVPacket, stream_index) p stream_index ; (#poke
(BAVPacket, flags) p flags;
(B   (#poke AVPacket, duration) p duration}
(BsizeOf _  = (#size AVPacket)
(B-- I don't confident this value.
(Balignment _ = 7
(B
(B
(Bav_init_packet :: IO (Ptr CAVPacket)
(Bav_init_packet =
(B  alloca $ \pkt - do
(B  c_av_init_packet pkt
(B  return pkt
(B
(B
(Bforeign import ccall unsafe "av_init_packet"
(Bc_av_init_packet :: Ptr CAVPacket - IO ()
(B-
(B
(Bbut ghc-6.2.2 said :
(B
(BFFmpeg.o(.text+0x44):fake: undefined reference to `av_init_packet' .
(B
(BOf cource, this problem is only here, ghc can refers to other C function
(Bby FFI. And if I don't pass the link option to ghc, then ghc's refer
(Bproblem message is normaly, like this :
(B
(Bc:/ghc/ghc-6.2.2/libHSrts.a(Main.o)(.text+0x87):Main.c: undefined
(Breference to `__stginit_ZCMain'
(B
(B
(BWhere is a problem of my code?
(B
(B
(B-- 
(Bshelarcy shelarcy capella.freemail.ne.jp
(Bhttp://page.freett.com/shelarcy/
(B___
(BHaskell-Cafe mailing list
(BHaskell-Cafe@haskell.org
(Bhttp://www.haskell.org/mailman/listinfo/haskell-cafe