[Haskell-cafe] Gtk2Hs + Sourceview on Windows

2009-05-19 Thread mwinter
Hi,

I have ghc 6.10.1 and gtk2hs 0.10.0 installed on my windows vista
computer. Both were installed using the installer on the webpages.
I am able to use gtk, glade etc but not sourceview or cairo. If I
compile the examples in the gtk2hs example folder, I get not in 
scope error messages for functions from those library components.
In a forum I found that those have to be enabled using 
./configure --enable-sourceview
(similar for cairo). But my windows installation does not seem to
have a script configure or a similar program. What am I supposed 
to do?

Thanks,
Michael

--
Michael WinterBrock University
Associate Professor500 Glenridge Avenue
Department of Computer Science  St. Catharine, ON, L2S 3 A1
Phone: +1 905 688 5550 ext 3355  Fax: +1 905 688 3255
-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Parsec - Custom Fail

2009-05-05 Thread mwinter
Hi,

I am using parsec to parse a small programming language. The language is typed 
and
I need to do some type checking, too. I have decided to do the parsing and type 
checking
simultaneously in the my parsec parser. This approach avoids to keep source 
code positions
in the data type in order to produce suitable error messages during type 
checking. Anyhow,
because type errors are usually detected after parsing some code I need produce 
error
messages with an earlier source position. Unfortunately, there is no function 
that produces 
an error taking a position as parameter. 

I tried the following:

myFail :: SourcePos - String - GenParser tok st a
myFail pos msg = setPosition pos  fail msg

This is already a workaround because I am modifying the position in the parser 
just to
produce an error message. But even worse, it does not work. If I use this 
function as in:

test :: Either ParseError ()
test = runParser (char '('  myFail (newPos  100 100) Test) ()  (

the position of the error is still the original position (line 1, column 2). As 
far as I can tell
setPosition does not take effect until another symbol is read. This could be 
achieved by
simply using anyToken if we are not at the end of the input (as in the example 
above). I
came up with the following:

myFail :: SourcePos - String - GenParser Char st a
myFail pos msg = do {
 State toks _ st - getParserState;
 setParserState $ State ('d':toks) pos st;
 anyToken;
 fail msg
  }

This code works but it is not nice at all. The function myFail is not longer 
polymorphic in
the type of tokens since we need an element of this data type in order to add 
it temporarily
to the input ('d' above).

My guess is that one has to enforce strictness at some point in order to work 
with the first
approach, but I was not successful. Any ideas?

Thanks,
Michael


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


Re: [Haskell-cafe] Parsec - Custom Fail

2009-05-05 Thread mwinter
Thanks, but I want a nice solution not another, even more complicated, 
workaround.

On 5 May 2009 at 17:10, Martijn van Steenbergen wrote:

 mwin...@brocku.ca wrote:
  Hi,
  
  I am using parsec to parse a small programming language. The language is 
  typed and
  I need to do some type checking, too. I have decided to do the parsing and 
  type checking
  simultaneously in the my parsec parser. This approach avoids to keep source 
  code positions
  in the data type in order to produce suitable error messages during type 
  checking. Anyhow,
  because type errors are usually detected after parsing some code I need 
  produce error
  messages with an earlier source position. Unfortunately, there is no 
  function that produces 
  an error taking a position as parameter. 
 
 If you already know what position you want to report the error at, then 
 why bother calling setPosition to let parsec know? Just do:
 
   fail (show pos ++ :  ++ msg)
 
 Parsec will then result in a ParseError with its own ideas of location, 
 but you can ignore that.
 
 HTH,
 
 Martijn.


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


[Haskell-cafe] Threading and Mullticore Computation

2009-03-03 Thread mwinter
Hi,

I tried a get into concurrent Haskell using multiple cores. The program below
creates 2 task in different threads, executes them, synchronizes the threads
using MVar () and calculates the time needed.  

import System.CPUTime
import Control.Concurrent
import Control.Concurrent.MVar

myTask1 = do
return $! fac 6
print Task1 done!
  where fac 0 = 1
fac n = n * fac (n-1)
  
myTask2 = do
return $! fac' 6 1 1
print Task2 done!
  where fac' n m p = if  mn then p else fac'  n (m+1) (m*p)

main = do
 mvar - newEmptyMVar
 pico1 - getCPUTime
 forkIO (myTask1  putMVar mvar ())
 myTask2
 takeMVar mvar
 pico2 - getCPUTime
 print (pico2 - pico1)
 

I compiled the code using 
$ ghc FirstFork.hs -threaded
and executed it by
$ main +RTS -N1   resp.   $ main +RTS -N2
I use GHC 6.8.3 on Vista with an Intel Dual Core processor. Instead of getting
a speed up when using 2 cores I get as significant slow down, even though there 
is no sharing in my code above (at least none I am aware of. BTW, that was 
reason 
that I use 2 different local factorial functions). On my computer the 1-core 
version 
takes about 8.3sec and the 2-core version 12.8sec. When I increase the numbers 
from 6 to 10 the time difference gets even worse (30sec vs 51 sec). Can 
anybody give me an idea what I am doing wrong?

Thanks,
Michael



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


Re: [Haskell-cafe] Threading and Mullticore Computation

2009-03-03 Thread mwinter
In both runs the same computations are done (sequentially resp.
parallel), so the gc should be the same. But still using 2 cores is
much slower than using 1 core (same program - no communication).

On 3 Mar 2009 at 20:21, Bulat Ziganshin wrote:

 Hello mwinter,
 
 Tuesday, March 3, 2009, 8:09:21 PM, you wrote:
 
 anybody give me an idea what I am doing wrong?
 
 1. add -O2 to compile command
 2. add +RTS -s to run commands
 
 your program execution time may be dominated by GCs
 
 
 -- 
 Best regards,
  Bulatmailto:bulat.zigans...@gmail.com


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


Re: [Haskell-cafe] Threading and Mullticore Computation

2009-03-03 Thread mwinter
It gets a bit faster in general but the problem remains. I have two
threads in both runs, once I use 1 core and then 2 cores. The second
run is much slower.

On 3 Mar 2009 at 17:32, Sebastian Sylvan wrote:

 
 
 
 On Tue, Mar 3, 2009 at 5:31 PM, mwin...@brocku.ca wrote:
 In both runs the same computations are done (sequentially resp.
 parallel), so the gc should be the same. But still using 2 cores is
 much slower than using 1 core (same program - no communication). 
 
 Might there not be contention in the allocator/GC that's worsened by having 
 two threads? 
 What happens with -O2?
 --
 Sebastian Sylvan
 +44(0)7857-300802
 UIN: 44640862 
 


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


Re: [Haskell-cafe] Threading and Mullticore Computation

2009-03-03 Thread mwinter
I am using GHC 6.8.3. The -O2 option made both runs faster but the 2 core run
is still much slower that the 1 core version. Will switching to 6.10 make the 
difference?

On 3 Mar 2009 at 18:46, Svein Ove Aas wrote:

 On Tue, Mar 3, 2009 at 6:41 PM, Don Stewart d...@galois.com wrote:
  allbery:
  On 2009 Mar 3, at 12:31, mwin...@brocku.ca wrote:
  In both runs the same computations are done (sequentially resp.
  parallel), so the gc should be the same. But still using 2 cores is
  much slower than using 1 core (same program - no communication).
 
  The same GCs are done, but GC has to be done on a single core
  (currently; parallel GC is in development) so you will see a lot more
  lock contention when the GC kicks in.
 
 
  Assuming he is using GHC 6.10, the parallel GC is enabled by default
  when you use -Nn where n  1. That's is -N4 will use -g4   (4 cores to
  collect). So GC should be the same or a little faster.
 
 Further, GHC (6.10 at least) uses one allocation area per thread,
 meaning there's no contention on allocation.

 I'd echo the request to try it with -O2, though.
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


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