Hi there.
Could somebody please let me know where I've gone wrong in the program below
(yesterday's CVS HEAD stage 3 compiler on Windows)?
- TH - printf.hs ---
module Main where
import Language.Haskell.THSyntax
data Format = D | S | L String
main = putStrLn ( $(pr "Hello") )
pars
Nice design, Alastair. I've stolen lots of ideas and some text for the
complete rewrite of the proposal. The concept of "associating" haskell
threads to native threads proved to be a good way of explaining my
original idea in a different way --- and then I found out that
forkNativeThread needn'
At 2002-11-26 09:37, Alastair Reid wrote:
> 1) forkNativeThread :: IO () -> IO ()
> The fresh Haskell thread is bound to a fresh native thread.
>
> 2) forkIO :: IO () -> IO ()
> The fresh Haskell thread is not bound to a native thread.
Are you sure you intend to change the type of forkI
On Fri, 22 Nov 2002, Hal Daume III wrote:
> Because List is the H98 module, Data.List is the extended one which
> contains foldl'. Regardless of whether you say -package data or not,
> you're not going to get Data.List unless you ask for it explicitly:
(snip)
Thanks very much indeed! I finally h
On 26 Nov 2002, Alastair Reid wrote:
> > Umm, Alastair, I think you've got things a bit mixed up here. Did
> > you mean two ways to create a native thread?
>
> No.
>
> > There are currently three ways to create a Haskell thread (forkIO,
> > foreign export, finalizers) and Wolfgang has proposed
> Umm, Alastair, I think you've got things a bit mixed up here. Did
> you mean two ways to create a native thread?
No.
> There are currently three ways to create a Haskell thread (forkIO,
> foreign export, finalizers) and Wolfgang has proposed a fourth
> (forkNativeThread).
I was (implicitly)
> *
> Native Threads Proposal, version 2
>
> Some "foreign" libraries (for example OpenGL) rely on a mechanism
> called thread-local storage. The meaning of an OpenGL call therefore
> usually depends on which OS thread it is called from.
> Therefore, some
> kind of direct ma
On Tue, 2002-11-26 at 08:32, Dean Herington wrote:
> On 26 Nov 2002, Alastair Reid wrote:
>
> > ps Better names than 'native' and 'green' surely exist. Something
> > which conveys the idea that the thread will be remembered for later
> > use seems appropriate but no good words spring to mind.
>
Alastair Reid wrote:
> Design
> ~~
>
> Haskell threads may be associated at thread creation time with either
> zero or one native threads. There are only two ways to create Haskell
> threads so there are two cases to consider:
Umm, Alastair, I think you've got things a bit mixed up here. Di
On 26 Nov 2002, Alastair Reid wrote:
> ps Better names than 'native' and 'green' surely exist. Something
> which conveys the idea that the thread will be remembered for later
> use seems appropriate but no good words spring to mind.
Perhaps "bound" and "free"?
_
After sending this mail this morning, I realized that threadsafety is
largely orthogonal to the choice of which thread to run in. For
example, I might want to make an 'unsafe' call in a particular native
thread.
So my proposed spec should add a second, orthogonal choice of ffi call
types ('nativ
After writing a fairly long, detailed reply (attached at end), I
decided it would be simpler to write my take on what the design should
be.
Goals
~
Since foreign libraries sometimes exploit thread local state, it is
necessary to provide some control over which thread is used to execute
fore
Nicolas Oury <[EMAIL PROTECTED]> writes:
> * I think that, if it is not too much complicated, it could be great
> to put many threads in the OpenGL OS thread. The goal of concurrent
> Haskell was to allow concurrency for expressivity. It would be a
> pity to lose this in part of programs for tech
At the moment you have to build from source to get it, or you can grab a
development snapshot binary, from
http://haskell.cs.yale.edu/ghc/download.html
We're swithering about when to do a full release. Template Haskell is
still moving, and making a release takes time. We'll be strongly
affected
14 matches
Mail list logo