Hi,
I found and fixed this space leak in the Fudget library (it was a malloc without
free).
Thomas H
Simon Marlow wrote:
Dimitry Golubovsky wrote:
I wrote a very simple Fudgets program (just copies stdin to stdout, no
graphics involved)
I found out that the program grows in memory.
basic
Simon Marlow wrote:
Michael Marte wrote:
Lennart Augustsson wrote:
I'm not implying anything, except that I've plugged the space
leak of 256M every time a DLL is loaded&unloaded.
-- Lennart
Michael Marte wrote:
Lennart,
do you imply that you have fixed the problem causing the crashe
Hello Simon,
Thursday, March 9, 2006, 5:08:09 PM, you wrote:
>>>for small "home" projects you can even use "Int" and "int" which
>>>would work in most of Haskell implementations
SM> Yes, and to give a concrete example: HsInt and int are different types
SM> on x86_64 (and most other 64-bit C imp
* Li, Peng <[EMAIL PROTECTED]>:
> In GHC, how can I allocate a chunk of memory aligned to some block
> size (say, 512 or 1024 bytes)? I tried to specify it in the
> "alignment" method in the Storable typeclass, but that does not seem
> to work. Is Storable.alignment really used in GHC? If so, is th
No, the timer thread starts even without -threaded.
If you use -threaded it gets worse because then you have
a bunch of other threads that don't exit properly.
-- Lennart
Quoting Simon Marlow <[EMAIL PROTECTED]>:
Lennart Augustsson wrote:
I've found more bugs. There are several race condit
For the moment I am using the C function memalign() like this:
foreign import ccall "static stdlib.h"
memalign :: CInt -> CInt -> IO (Ptr CChar)
iirc, memalign is not provided on windows, nor by mingw.
so this wouldn't be portable.
claus
Storable.alignment is not used, it is there for inform
Dimitry Golubovsky wrote:
I wrote a very simple Fudgets program (just copies stdin to stdout, no
graphics involved)
leaktest.hs --
module Main where
import Graphics.UI.Fudgets.Fudgets
main = fudlogue (stdoutF >==< stdinF)
and ran it like this:
yes | leaktest
I fou
Sven Panne wrote:
Am Donnerstag, 9. März 2006 08:46 schrieb Bulat Ziganshin:
Thursday, March 9, 2006, 2:20:00 AM, you wrote:
foreign import ccall duma_init :: Int -> IO Int
MQK> HsInt duma_init(HsInt arg);
MQK> Or use int on the C side and CInt on the Haskell side.
MQK> fromIntegral can be
Li, Peng wrote:
[1] Extending the Haskell Foreign Function Interface with Concurrency
[2] Haskell on a Shared-Memory Multiprocessor
I read the above two papers [1,2] and I have been trying to write an
application that uses both FFI and SMP. The first paper [1] shows how
FFI is implemented on uni
Li, Peng wrote:
In GHC, how can I allocate a chunk of memory aligned to some block
size (say, 512 or 1024 bytes)? I tried to specify it in the
"alignment" method in the Storable typeclass, but that does not seem
to work. Is Storable.alignment really used in GHC? If so, is there a
code example tha
Bulat Ziganshin wrote:
Hello Simon,
Friday, March 3, 2006, 4:51:04 PM, you wrote:
is there an option to get ghc to keep going if it encounters an error
building a file with --make? as in, I'd like it to continue compiling as
much as it can only skipping what actually depends on the file that
f
Michael Marte wrote:
Lennart Augustsson wrote:
I'm not implying anything, except that I've plugged the space
leak of 256M every time a DLL is loaded&unloaded.
-- Lennart
Michael Marte wrote:
Lennart,
do you imply that you have fixed the problem causing the crashes?
May I safely assume
Lennart Augustsson wrote:
I've found more bugs. There are several race conditions when a DLL
is unloaded. The extra threads that the GHC runtime system starts
(at least one is always started to generate timer ticks) are not
shut down in a synchronized way. This means that they might be
schedu
Michael,
I've found more bugs. There are several race conditions when a DLL
is unloaded. The extra threads that the GHC runtime system starts
(at least one is always started to generate timer ticks) are not
shut down in a synchronized way. This means that they might be
scheduled to run after t
Am Donnerstag, 9. März 2006 08:46 schrieb Bulat Ziganshin:
> Thursday, March 9, 2006, 2:20:00 AM, you wrote:
> >> foreign import ccall duma_init :: Int -> IO Int
>
> MQK> HsInt duma_init(HsInt arg);
> MQK> Or use int on the C side and CInt on the Haskell side.
> MQK> fromIntegral can be used for co
Hello Marcin,
Thursday, March 9, 2006, 2:20:00 AM, you wrote:
>> foreign import ccall duma_init :: Int -> IO Int
MQK> HsInt duma_init(HsInt arg);
MQK> Or use int on the C side and CInt on the Haskell side.
MQK> fromIntegral can be used for converting integers in Haskell.
for small "home" proj
16 matches
Mail list logo