Gracjan Polak wrote:
Hi,
In the following code only processInit and processClose get ever called,
other callbacks are *never* invoked. Is this known problem? Do I miss
something obvious?
Forgotten: Windows 2000, GHC-6.2.1 :)
--
Pozdrawiam, Regards,
Gracjan
___
Hi,
In the following code only processInit and processClose get ever called,
other callbacks are *never* invoked. Is this known problem? Do I miss
something obvious?
How do I get the handle of main window?
Here is the code:
module Main where
import Graphics.UI.ObjectIO
processAttributes =
[
Hi,
I'm trying to make use of memory mapped files with Haskell. It is kind
of fun, I managed to mmap a file (actualy CreateFileMapping, because I'm
on a Windows box), managed to setup finalizers (those kind of work now,
see my posts about finalizers and FFI).
Now I got to content... and here is
"Simon Marlow" <[EMAIL PROTECTED]> writes:
> If a function is called, then the result has been demanded. There are
> no situations in which a function has been called but the caller will
> accept a thunk as the result without further evaluating it.
> The caller would definitely have to evaluate i
it means Lazy, but it's misleading for unboxed types
| -Original Message-
| From: [EMAIL PROTECTED]
[mailto:glasgow-haskell-users-
| [EMAIL PROTECTED] On Behalf Of Adrian Hey
| Sent: 22 June 2004 17:09
| To: [EMAIL PROTECTED]
| Subject: Re: Understanding strictness of ghc output
|
| On Tu
On Tuesday 22 Jun 2004 2:28 pm, Simon Peyton-Jones wrote:
> The DmdType for the Int# is indeed "L" but that's irrelevant because
> Int# values are always evaluated. The demand info is always L for an
> unboxed type.
Thanks, I had noticed it did appear to have decided h was unboxed
(assuming my in
On 22 June 2004 15:59, Malcolm Wallace wrote:
> "Simon Marlow" <[EMAIL PROTECTED]> writes:
>
>> Nope. You can't return something without evaluating it to head
>> normal form in Haskell. Every value that is "returned" is a value,
>> never a thunk. If you want to return something unevaluated, yo
On Tue, Jun 22, 2004 at 02:28:21PM +0100, Simon Peyton-Jones wrote:
> | That contradicts my intution for seq. I would read it as "h is forced
> | before h is forced", and I would think that (h `seq` h) is equivalent
> | to h.
> |
> | Were I am wrong?
>
> You're not wrong -- Malcolm is. The funct
"Simon Marlow" <[EMAIL PROTECTED]> writes:
> Nope. You can't return something without evaluating it to head normal
> form in Haskell. Every value that is "returned" is a value, never a
> thunk. If you want to return something unevaluated, you have to wrap it
> in a constructor.
Actually, there
On Tue, Jun 22, 2004 at 03:37:01PM +0100, Simon Marlow wrote:
> If there's a Haskell implementation that compiles addHeight in such a
> way that addHeight _|_ e /= _|_, then I'd say it was wrong (but we
> don't have an official denotational semantics for Haskell, only an
> informal agreement ;-).
On 22 June 2004 15:11, Duncan Coutts wrote:
> On Tue, 2004-06-22 at 14:17, Tomasz Zielonka wrote:
>> On Tue, Jun 22, 2004 at 01:52:44PM +0100, Malcolm Wallace wrote:
>>>
>>> Same again. Try
>>>addHeight h E= h `seq` h
>>>
>>> which, although it looks bizarre, actually forces the ev
On Tue, 2004-06-22 at 14:17, Tomasz Zielonka wrote:
> On Tue, Jun 22, 2004 at 01:52:44PM +0100, Malcolm Wallace wrote:
> >
> > Same again. Try
> >addHeight h E= h `seq` h
> >
> > which, although it looks bizarre, actually forces the evaluation of h,
> > whilst simply returning it do
On Tue, Jun 22, 2004 at 02:37:38PM +0100, Malcolm Wallace wrote:
> "Simon Peyton-Jones" <[EMAIL PROTECTED]> writes:
>
> > | That contradicts my intution for seq. I would read it as "h is forced
> > | before h is forced", and I would think that (h `seq` h) is equivalent
> > | to h.
> > |
> > | Wer
| Well, it is certainly the case that in a denotational sense the
| function is strict in h, because if h is bottom, the result is bottom.
Right. And GHC's operational behaviour is faithful to the denotational
semantics. When GHC compiles the program, if h is bottom, the call will
not return.
Si
"Simon Peyton-Jones" <[EMAIL PROTECTED]> writes:
> | That contradicts my intution for seq. I would read it as "h is forced
> | before h is forced", and I would think that (h `seq` h) is equivalent
> | to h.
> |
> | Were I am wrong?
>
> You're not wrong -- Malcolm is. The function is certainly s
| That contradicts my intution for seq. I would read it as "h is forced
| before h is forced", and I would think that (h `seq` h) is equivalent
| to h.
|
| Were I am wrong?
You're not wrong -- Malcolm is. The function is certainly strict in h,
and GHC finds it.
Here's what I get when I compil
On Tue, Jun 22, 2004 at 01:52:44PM +0100, Malcolm Wallace wrote:
>
> Same again. Try
>addHeight h E= h `seq` h
>
> which, although it looks bizarre, actually forces the evaluation of h,
> whilst simply returning it does not.
That contradicts my intution for seq. I would read it as
On Tue, Jun 22, 2004 at 01:52:44PM +0100, Malcolm Wallace wrote:
> Adrian Hey <[EMAIL PROTECTED]> writes:
> [...] the first clause
>addHeight h E= h
> is still lazy, because it simply binds the variable without forcing it.
Since addHeight _|_ E -> _|_, this is strict in the first arg
Adrian Hey <[EMAIL PROTECTED]> writes:
> height :: AVL e -> Int
> height = addHeight 0 where
> addHeight h E= h
> addHeight h (N l _ _) = addHeight h+2 l
> addHeight h (Z l _ _) = addHeight h+1 l
> addHeight h (P _ _ r) = addHeight h+2 r
>
> It seems pretty obvious to me that add
On 22 June 2004 13:30, Adrian Hey wrote:
> I'm trying to figure out how you tell if ghc has correctly infered
> strictness or whether or not a little more prompting from me
> is needed.
>
> I tried compiling with -ddump-simpl, and I guess from looking
> at this the DmdType bit is what I want (may
On 22 June 2004 12:24, Volker Stolz wrote:
> In local.glasgow-haskell-users, you wrote:
>> On 22 June 2004 10:39, Bernard James POPE wrote:
>>> Supposing that such a thing is indeed possible is there any chance
>>> that it could be folded into GHC? (Then I wouldn't have to ship my
>>> own variant
Hello,
I'm trying to figure out how you tell if ghc has correctly infered
strictness or whether or not a little more prompting from me
is needed.
I tried compiling with -ddump-simpl, and I guess from looking
at this the DmdType bit is what I want (maybe). So if I have
"DmdType LS" for a function
In local.glasgow-haskell-users, you wrote:
> On 22 June 2004 10:39, Bernard James POPE wrote:
>> Supposing that such a thing is indeed possible is there any chance
>> that it could be folded into GHC? (Then I wouldn't have to ship my
>> own variant of the runtime with buddha.)
>
> Certainly, I don'
On 22 June 2004 10:39, Bernard James POPE wrote:
> Supposing that such a thing is indeed possible is there any chance
> that it could be folded into GHC? (Then I wouldn't have to ship my
> own variant of the runtime with buddha.)
Certainly, I don't see any reason why not. It looks like a bolt-on
On Tue, Jun 22, 2004 at 09:45:48AM +0100, Simon Marlow wrote:
> On 22 June 2004 06:11, Bernard James POPE wrote:
>
> > Ideally I'd like this function:
> >
> >blockThread :: ThreadId -> IO ()
> >
> > and thus:
> >
> >unBlockThread :: ThreadId -> IO ()
>
> Hmm, might be possible. Can th
On Tue, Jun 22, 2004 at 10:37:54AM +0200, Volker Stolz wrote:
> In local.glasgow-haskell-users, you wrote:
> > Ideally I'd like this function:
> >blockThread :: ThreadId -> IO ()
> >unBlockThread :: ThreadId -> IO ()
>
> I should have some bit-rotted patches here for
> freezeThread :: Thre
On Tue, Jun 22, 2004 at 09:27:40AM +0100, Simon Marlow wrote:
> On 22 June 2004 03:51, Bernard James POPE wrote:
>
> > The mblocks_allocated variable should give me what I want.
> >
> > I think having access to this would also be useful to people who are
> > profiling their programs. You see a fe
On Tue, Jun 22, 2004 at 09:27:40AM +0100, Simon Marlow wrote:
> On 22 June 2004 03:51, Bernard James POPE wrote:
>
> > The mblocks_allocated variable should give me what I want.
> >
> > I think having access to this would also be useful to people who are
> > profiling their programs. You see a fe
On 22 June 2004 06:11, Bernard James POPE wrote:
> Ideally I'd like this function:
>
>blockThread :: ThreadId -> IO ()
>
> and thus:
>
>unBlockThread :: ThreadId -> IO ()
Hmm, might be possible. Can the blocked thread be woken up by an
exception? (this is usually the case for blocked
In local.glasgow-haskell-users, you wrote:
> Ideally I'd like this function:
>blockThread :: ThreadId -> IO ()
>unBlockThread :: ThreadId -> IO ()
I should have some bit-rotted patches here for
freezeThread :: ThreadId -> IO ()
thawThread :: ThreadId -> IO () and a new PrimOp which
allow
On 22 June 2004 03:51, Bernard James POPE wrote:
> The mblocks_allocated variable should give me what I want.
>
> I think having access to this would also be useful to people who are
> profiling their programs. You see a few papers where people want to
> report how much memory their application n
31 matches
Mail list logo