Re: Optimisation and unsafePerformIO

2002-10-29 Thread Albert Lai
"David Sabel" <[EMAIL PROTECTED]> writes:

> {-# NOINLINE b #-}
> 
> b x  = if even x then unsafePerformIO getChar else bot
> 
> bot = bot
> 
> main = do
>  putChar (b 4)
>  putChar (b 6)

I am not a compiler implementer (or lawyer, for that matter :)
But I propose this guess.  First, both even 4 and even 6 get
constant-folded to True; so b 4 and b 6 both become unsafePerformIO
getChar.  Then there is a common subexpression elimination.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: FFI & C++

2002-10-29 Thread Alastair Reid

> Hi, I am currently trying to create a Haskell interface to a C++
> library and cannot get it to work completely.

If you want to interface Hugs to C++ code, you have to link Hugs using
a C++ compiler so that the Hugs binary contains new, throw, etc.  I
believe the main thing this changes is that some extra libraries are
linked into the binary.

Obviously, the story is a bit different for GHC but you probably want to either:

1) Tell GHC to use a C++ compiler as its linker; or

2) Figure out what libraries C++ adds in (e.g., compare what g++ -v
   and gcc -v do with hello world) and tell GHC to use them when linking.

--
Alastair Reid [EMAIL PROTECTED]  
Reid Consulting (UK) Limited  http://www.reid-consulting-uk.ltd.uk/alastair/

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



problem generating Core with no-implicit-prelude

2002-10-29 Thread Hal Daume III
Hi all,

I think there's a problem with the external core generation.  Suppose we
have the following module:

-
module Test where

data Bool = True | False
data Maybe a = Just a | Nothing

class Eq a where
(==) :: a -> a -> Bool

instance Eq Bool where
(==) True  True  = True
(==) False False = True
(==) _ _ = False

instance Eq a => Eq (Maybe a) where
(==) Nothing  Nothing  = True
(==) (Just a) (Just b) = (==) a b
(==) __= False
-

We compile this using:
  ghc -fext-core -fno-code test.hs -fno-implicit-prelude

Now, if we look at the core, inside the definition of Test.zdfEqMaybe (the
eq function for Maybe a), it essentially looks like (glossing over some of
the extraneous stuff):

  Test.zdfEqMaybe = \ zddEq -> Test.ZCDEq
\ ds ds1 ->
 case ds of
   Nothing -> case ds1 of
Test.Just a1 -> Test.zdwFalse
Test.Nothing -> Test.zdwTrue
   Just a1 -> case ds1 of
Test.Nothing -> Test.zdwFalse
Test.Just b  -> Test.zeze zddEq a1 b

Now, the problem is that "Test.ZCDEq" isn't defined anywhere in the core
file produced and neither is Test.zeze.

If this is indeed a bug, could someone fix it?  If not, could someone tell
me what I'm doing wrong (I could be misreading the Core, but I don't think
so).

 - Hal

p.s., the full core output reads:

%module Test
  %data Test.Bool =
{Test.True;
 Test.False};
  %data Test.Maybe a =
{Test.Just a;
 Test.Nothing};
  %newtype Test.ZCTEq a = GHCziPrim.ZLzmzgZR
  a
  (GHCziPrim.ZLzmzgZR a Test.Bool);
  Test.zdfEqBool :: GHCziPrim.ZLzmzgZR
Test.Bool
(GHCziPrim.ZLzmzgZR Test.Bool Test.Bool) =
\ (ds::Test.Bool) (ds1::Test.Bool) ->
%case ds %of (wild::Test.Bool)
  {Test.False ->
 %case ds1 %of (wild1::Test.Bool)
   {Test.True ->
  Test.zdwFalse;
Test.False ->
  Test.zdwTrue};
   Test.True ->
 ds1};
  Test.zdfEqMaybe :: %forall a . GHCziPrim.ZLzmzgZR
 (GHCziPrim.ZLzmzgZR a (GHCziPrim.ZLzmzgZR
a Test.Bool))
 (GHCziPrim.ZLzmzgZR
  (Test.Maybe a)
  (GHCziPrim.ZLzmzgZR (Test.Maybe
a) Test.Bool)) =
%note "InlineMe"
\ @ a
  (zddEq::GHCziPrim.ZLzmzgZR a (GHCziPrim.ZLzmzgZR a Test.Bool)) ->
Test.ZCDEq @ (Test.Maybe a)
(\ (ds::Test.Maybe a) (ds1::Test.Maybe a) ->
 %case ds %of (wild::Test.Maybe a)
   {Test.Nothing ->
  %case ds1 %of (wild1::Test.Maybe a)
{Test.Just (a1::a) ->
   Test.zdwFalse;
 Test.Nothing ->
   Test.zdwTrue};
Test.Just (a1::a) ->
  %case ds1 %of (wild1::Test.Maybe a)
{Test.Nothing ->
   Test.zdwFalse;
 Test.Just (b::a) ->
   Test.zeze @ a zddEq a1 b}});

--
Hal Daume III

 "Computer science is no more about computers| [EMAIL PROTECTED]
  than astronomy is about telescopes." -Dijkstra | www.isi.edu/~hdaume

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



FFI & C++

2002-10-29 Thread Niklas Sörensson
Hi,

I am currently trying to create a Haskell interface to a C++ library and
cannot get it to work completely. The problem seems to be that the linker
must be able to find the code for basic C++ constructs like new and throw.
Apparently it is able to do so when compiling an executable, but when I
try to do the same with ghci it fails. Anybody have an idea why this
happens and what to do about it?

A second question,

The feature to install local packages is currently a bit awkward. I would
like to be able to simply use a local package the same way I use a normal
package, and my first try was to set the package-conf file in my .ghci
file. But this doesn't work very well for two reasons: (1) it only works
for the interpreter, but not for the compiler (2) it isn't read until
*after* the command line is read, so any packages given there is not
recognized. Is it possible to have a common (.ghc) file that is used for
both the compiler and the interpreter, and that is read *before* the
command line is interpreted?

/Niklas

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



RE: crash in profiling mode

2002-10-29 Thread Simon Marlow
> I have a problem with profiling using a freshly installed GHC 
> 5.04 under Solaris. With the following program crash.lhs:

Please install 5.04.1 instead, I believe this bug was fixed.

Cheers,
Simon
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



crash in profiling mode

2002-10-29 Thread Janis Voigtlaender
Hello,

I have a problem with profiling using a freshly installed GHC 5.04 under
Solaris. With the following program crash.lhs:

> module Main where

> test1 = print "test1"

> test2 = {-# SCC "test2" #-} print "test2"

> main = do c <- readLn
>   if c==1 then test1 else test2

I get the following runs:

~> ghc-5.04 -prof crash.lhs
~> ./a.out 
1
"test1"

~> ./a.out
2
Bus error
Exit 138

So, code compiled with a cost-center annotation crashes (note that I
didn't even run the compiled program in profiling mode). The same
happens, when compiler flags -auto or -auto-all are used. Hence, the
profiling facilities are useless on my installation.

Has anyone experienced such problem before? What could be broken with my
installation? Some library problems?

Any hint appreciated.

Regards, Janis.

--
Janis Voigtlaender
http://wwwtcs.inf.tu-dresden.de/~voigt/
mailto:voigt@;tcs.inf.tu-dresden.de
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users