duncan.coutts:
> This sort of code runs very slowly when compared to the equivalent in C:
This example uses unboxing and primops over Lemmih's and seems to run a bit
faster:
Lemmih's loops:
./a.out 1.35s user 0.00s system 99% cpu 1.359 total
This code:
./a.out 0.99s user 0.00s
Hello,
I am not sure if this is the correct place to report this problem, but
there is a bug in the Cabal distributed with GHC. I used the simplest
possible Setup.hs file as shown in the documentation.
All the modules in my library are in a directory Monad, e.g.
Monad/State.hs, Monad/Reader.hs, et
On Tue, 2005-03-15 at 02:06 +0100, Lemmih wrote:
> We can make it a little faster by not doing bound checks:
>
> > test4 :: IO ()
> > test4 = do
> > (arr :: IOUArray Int Bool) <- newArray_ (0,100*100-1)
> > doFromTo 0 $ \_ ->
> > doFromTo 0 99 $ \y ->
> > doFromTo 0 99 $ \x ->
>
On Tue, 2005-03-15 at 01:39 +0100, Josef Svenningsson wrote:
> Hi,
>
> On Mon, 14 Mar 2005 13:41:06 +, Duncan Coutts
> <[EMAIL PROTECTED]> wrote:
> > This sort of code runs very slowly when compared to the equivalent in C:
> >
> I'm afraid the kind of array processing code you posted will alw
This one might go even faster again.
Essentially due to Don Stewart but removes the bound checks and uses
Int as an index.
-
module Main
where
import Data.Array.MArray
import Data.Array.IO
import Data.Array.Base
import GHC.Base
import GHC.IOBase
forn a n | n >=# 1# = return ()
On Tue, 15 Mar 2005 02:06:06 +0100, Lemmih <[EMAIL PROTECTED]> wrote:
> We can make it a little faster by not doing bound checks:
>
> > test4 :: IO ()
> > test4 = do
> > (arr :: IOUArray Int Bool) <- newArray_ (0,100*100-1)
> > doFromTo 0 $ \_ ->
> > doFromTo 0 99 $ \y ->
> > do
We can make it a little faster by not doing bound checks:
> test4 :: IO ()
> test4 = do
> (arr :: IOUArray Int Bool) <- newArray_ (0,100*100-1)
> doFromTo 0 $ \_ ->
> doFromTo 0 99 $ \y ->
> doFromTo 0 99 $ \x ->
> unsafeWrite arr (x*(y+1)) False
Timings (compiled with
Hi,
On Mon, 14 Mar 2005 13:41:06 +, Duncan Coutts
<[EMAIL PROTECTED]> wrote:
> This sort of code runs very slowly when compared to the equivalent in C:
>
I'm afraid the kind of array processing code you posted will always be
slower than the C "equivalent". Haskell only has safe array meaning
On Mon, 2005-03-14 at 13:41 +, Duncan Coutts wrote:
> Hi,
>
> This sort of code runs very slowly when compared to the equivalent in C:
[snip]
BTW These timings were for ghc 6.2.2
My version of ghc 6.3 (CVS from about a month or two ago) gave slightly
beter timings on both loop version.
My
Bugs item #1163215, was opened at 2005-03-14 20:29
Message generated for change (Tracker Item Submitted) made by Item Submitter
You can respond by visiting:
https://sourceforge.net/tracker/?func=detail&atid=108032&aid=1163215&group_id=8032
Category: None
Group: None
Status: Open
Resolution: None
Yong Luo <[EMAIL PROTECTED]> writes:
> I installed a very old version of GHC in the same laptop in 2001 and it was
> working well ("no matter how big the program was"). Now, I upgraded it to
> version 6.2.2, but it becomes very slow and asks more Memory or Space.
Well, if you are using mainly s
Hi,
This sort of code runs very slowly when compared to the equivalent in C:
> {-# OPTIONS -fglasgow-exts #-}
> module Main where
>
> import Data.Array.MArray
> import Data.Array.IO
>
> data Pos = Pos !Int !Int
> deriving (Eq, Ord, Ix)
>
> main = test1
>
> test1 :: IO ()
> test1 = do
> (a
Bugs item #1163018, was opened at 2005-03-14 06:16
Message generated for change (Tracker Item Submitted) made by Item Submitter
You can respond by visiting:
https://sourceforge.net/tracker/?func=detail&atid=108032&aid=1163018&group_id=8032
Category: Profiling
Group: None
Status: Open
Resolution:
You're quite right. GHC has a simple but non-performant representation
of type synonyms in types, so as to be able to generate good error
messages, In particular, the type
S t
where S is a type synonym defined by 'type S a = s', is represented as
SynNote (S t) (s [t/a])
That i
Bugs item #1162969, was opened at 2005-03-14 12:56
Message generated for change (Tracker Item Submitted) made by Item Submitter
You can respond by visiting:
https://sourceforge.net/tracker/?func=detail&atid=108032&aid=1162969&group_id=8032
Category: Compiler
Group: None
Status: Open
Resolution: N
Bugs item #1162965, was opened at 2005-03-14 12:54
Message generated for change (Tracker Item Submitted) made by Item Submitter
You can respond by visiting:
https://sourceforge.net/tracker/?func=detail&atid=108032&aid=1162965&group_id=8032
Category: Compiler (Type checker)
Group: None
Status: Ope
> > But if Main.hs is big, it will give me a message, "Killed" , after a
> > long time running.
> > PIII, 64M memory
> Anyone know what is going on here?
The message "Killed" means your machine ran out of virtual memory.
Since you have only 64M real memory, I would guess your virtual
(=real+swap
An entirely sensible suggestion, too late for 6.4, but a good feature
request for the next version.
Simon
| -Original Message-
| From: [EMAIL PROTECTED]
[mailto:glasgow-haskell-bugs-
| [EMAIL PROTECTED] On Behalf Of Brian Smith
| Sent: 09 March 2005 08:58
| To: glasgow-haskell-bugs@hask
On 13 March 2005 13:23, John Tromp wrote:
> (tromp 999) ghci -v
>___ ___ _
> / _ \ /\ /\/ __(_)
> / /_\// /_/ / / | | GHC Interactive, version 6.4.20050301, for
> Haskell 98. / /_\\/ __ / /___| | http://www.haskell.org/ghc/
> \/\/ /_/\/|_| Type :? for help.
On 13 March 2005 01:06, Claus Reinke wrote:
> on windows xp sp2 with cygwin:
>
> - installed latest alex,happy,haddock from binaries on Sven's page
> (should this be mentioned in the building guide?
> http://www.aedion.de/haskell/ )
>
> - installed ghc 6.4, using msi in download area
>
(tromp 999) ghci -v
___ ___ _
/ _ \ /\ /\/ __(_)
/ /_\// /_/ / / | | GHC Interactive, version 6.4.20050301, for Haskell
98.
/ /_\\/ __ / /___| | http://www.haskell.org/ghc/
\/\/ /_/\/|_| Type :? for help.
Reading package config file:
/export/scratch1/trom
GHC 6.4 Final Release - tried the sample code for
Graphics.HGL, i.e.
module Main where {
import Graphics.HGL;
main :: IO ();
main = runGraphics $
withWindow_ "Hello World Window" (300, 200) $ \ w -> do
drawInWindow w $ text (100, 100) "Hello World"
drawInW
In gmane.comp.lang.haskell.glasgow.bugs, you wrote:
> ghc works for small programs, ie, if Main.hs is small then
> ghc --make Main.hs will give me a.out
> But if Main.hs is big, it will give me a message, "Killed" , after a
> long time running.
>
> PIII, 64M memory
> 420M free space on hard disk.
Anyone know what is going on here?
Simon
-Original Message-
From: Yong Luo [mailto:[EMAIL PROTECTED]
Sent: 11 March 2005 20:15
To: Simon Peyton-Jones
Subject: ghc, linux
Dear Simon,
I installed ghc-6.2.2 in my laptop by using the package
ghc-6.2.2-0.pm.0.i586.rpm
ghc works for small p
24 matches
Mail list logo