Re: Object Splitting and the Base Package Makefile

2002-10-14 Thread Michael Weber

* Wolfgang Thaller [EMAIL PROTECTED] [2002-10-09T00:42+0200]:
 When building the library archive libHSbase.a, the makefile system 
 includes not only all the split object files, but also the file 
 PrimopWrappers.o. Consequently [at least on Mac OS X], ranlib generates 
 a warning about duplicate symbols and fails to generate a sorted symbol 
 table for the library (it generates an unsorted symbol table instead, 
 which leads to slower linking).
 Happens with the current HEAD.

In a related issue, it seems that in ghc-5.04 libraries *_hsc.o files
are left out when linking with SplitObjs=YES.

michaelw@stargate:.../build-stage1/libraries/network$ rm libHSnetwork.a
michaelw@stargate:.../build-stage1/libraries/network$ make libHSnetwork.a
rm -f libHSnetwork.a libHSnetwork.a.tmp
(echo  cbits/ancilData.o; /usr/bin/find Network_split
Network/BSD_split Network/CGI_split Network/Socket_split
Network/URI_split -name '*.o') | xargs ar q libHSnetwork.a
: libHSnetwork.a
michaelw@stargate:.../build-stage1/libraries/network$ rm libHSnetwork.a
michaelw@stargate:.../build-stage1/libraries/network$ make libHSnetwork.a SplitObjs=NO
rm -f libHSnetwork.a
/usr/bin/ar clqslibHSnetwork.a  Network.o Network/BSD.o
Network/CGI.o Network/Socket.o Network/URI.o Network/BSD_hsc.o
Network/Socket_hsc.o cbits/ancilData.o 
: libHSnetwork.a
michaelw@stargate:.../build-stage1/libraries/network$ make show VALUE=EXTRA_OBJS
EXTRA_OBJS=cbits/ancilData.o
michaelw@stargate:.../build-stage1/libraries/network$ make show VALUE=C_OBJS
C_OBJS=Network/BSD_hsc.o Network/Socket_hsc.o cbits/ancilData.o
michaelw@stargate:.../build-stage1/libraries/network$

With SplitObjs=YES, Network/BSD_hsc.o and Network/Socket_hsc.o are
missing from the archive, since different linking commands are used.

After a short look into .../mk/target.mk, $(EXTRA_OBJS) seems to be
the culprit.

Can somebody please verify that it is indeed the case and the attached
fix doesn't break anything else (and do a check-in, if so)? (I'm a bit
short on time).


Cheers,
Michael
p.s.: is $(STUBOBJS) needed there?
___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs



[ ghc-Bugs-617082 ] ghc -O generates faulty c code

2002-10-14 Thread noreply

Bugs item #617082, was opened at 2002-10-01 15:47
You can respond by visiting: 
https://sourceforge.net/tracker/?func=detailatid=108032aid=617082group_id=8032

Category: Compiler
Group: 5.04
Status: Closed
Resolution: Duplicate
Priority: 5
Submitted By: Nobody/Anonymous (nobody)
Assigned to: Nobody/Anonymous (nobody)
Summary: ghc -O generates faulty c code

Initial Comment:
I have the following file:

Bug.hs
--
module Bug where

foo :: Double - Double
foo x = x - (-1.0) 
--

 ghc -c -O Bug.hs
/tmp/ghc25320.hc: In function `s3Ny_ret':
/tmp/ghc25320.hc:14: invalid lvalue in decrement
/tmp/ghc25320.hc:14: parse error before `1.0'

Cause
-

The problem is the following generated c snippet

_s3Nx_=PK_DBL((W_*)(R1.p+1))--1.0;

The two consecutive minuses should be separated by a
space.

Ulf Norell
[EMAIL PROTECTED]


--

Comment By: Simon Marlow (simonmar)
Date: 2002-10-14 12:47

Message:
Logged In: YES 
user_id=48280

This was fixed in 5.04.1 (also reported in #604849).

--

Comment By: Sven Panne (spanne)
Date: 2002-10-03 12:23

Message:
Logged In: YES 
user_id=50298

I've tested it with 5.02.3, 5.04.1 and the CVS HEAD and it
works fine in all cases (i.e.the literal is correctly
wrapped into parentheses). Which version are you using exactly?

--

You can respond by visiting: 
https://sourceforge.net/tracker/?func=detailatid=108032aid=617082group_id=8032
___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs



[ ghc-Bugs-620264 ] rdrNameModule it

2002-10-14 Thread noreply

Bugs item #620264, was opened at 2002-10-08 14:46
You can respond by visiting: 
https://sourceforge.net/tracker/?func=detailatid=108032aid=620264group_id=8032

Category: Compiler
Group: 5.04.1
Status: Closed
Resolution: Fixed
Priority: 5
Submitted By: Nobody/Anonymous (nobody)
Assigned to: Nobody/Anonymous (nobody)
Summary: rdrNameModule it

Initial Comment:
I´m new in this, and probably this is known... or maybe 
irrelevant:
What I´ve done: (in Prelude)

let x = error help!
print x
id x
print it

I did not understand why x isn´t printed (id x works...), 
but the serious ghc.exe panic! message after trying 
to 'print it' told me to report this ^_^
I just went through the manual and tried some lines out 
of it...

system: Win XP
version: 5.04.1 GHCi

E-Mail: [EMAIL PROTECTED]

--

Comment By: Simon Marlow (simonmar)
Date: 2002-10-14 12:52

Message:
Logged In: YES 
user_id=48280

The bug has been fixed; 5.04.2 will have the fix.  

To make print x work, you need to give x a type signature.  
eg.

  let x = error help! :: Int


--

You can respond by visiting: 
https://sourceforge.net/tracker/?func=detailatid=108032aid=620264group_id=8032
___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs



RE: ghc MacOS X 10.2 behaviour

2002-10-14 Thread Simon Peyton-Jones

[EMAIL PROTECTED] would be a better bet. 
Wolfgang Thaller is Supreme Being for MacOS so I'm cc'ing him too.

| -Original Message-
| From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED]]
| Sent: 14 October 2002 14:44
| To: [EMAIL PROTECTED]
| Subject: ghc MacOS X 10.2 behaviour
| 
| Hi all,
| 
| I'm working with Haskell on MacOS X 10.2.1 using the binaries from
| www.uni-graz.at/imawww/haskell.
| 
| Now, when I compile some code with ghc I get two errors:
| /tmp/ghc617.hc:283: conflicting types for
'GHCziTopHandler_runIO_closure'
| and
| /usr/local/lib/ghc-5.04/include/RtsAPI.h:125: previous declaration of
| 'GHCziTopHandler_runIO_closure'
| 
| Using ghci or compiling with -O2 doesn't show this error.
| 
| Any ideas what's wrong?
| 
| Thanks,
| Markus
| 
| By the way, if there is a list more suited for the subject, please
tell me.
| 
| 
| ___
| Haskell mailing list
| [EMAIL PROTECTED]
| http://www.haskell.org/mailman/listinfo/haskell
___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs



RE: [GHCi 5.04.1] the `impossible' happened

2002-10-14 Thread Simon Marlow

   [Indented text is me; unindented text is GHCi]
 
   Initial experience with the bug:
 
 *Autoexi let x e = do putStrLn hmm...; return 'c'
 *Autoexi y - catch (getChar) (x)
 
   here, I hit ^C several times, hoping to catch that as an exception.
   This didn't seem to happen, and GHCi appeared to still be waiting
   for a key, so I pressed 'h'
 
 hInterrupted.
 *Autoexi y
 ghc-5.04.1: panic! (the `impossible' happened, GHC version 5.04.1):
 rdrNameModule y
 
 Please report it as a compiler bug to 
 [EMAIL PROTECTED],
 or http://sourceforge.net/projects/ghc/.
 
   With a fresh GHCi:
 
 Prelude let x e = return 'c'
 Prelude y - catch (getChar) (x)
 
   GHCi responded immediately to my first ^C, here.
 
 Interrupted.
 Prelude y
 ghc-5.04.1: panic! (the `impossible' happened, GHC version 5.04.1):
 rdrNameModule y

There are two issues here:

  - the 'rdrNameModule' crash has been reported before, and the
fix will be in 5.04.2

  - the reason that ^C is not responded to immediately appears to
be due to a bad interaction with readline.  The readline library
puts the input descriptor into blocking mode if it finds it
in non-blocking mode, whereas GHC's IO library expects it to be
in non-blocking mode all the time.  We might be able to work
around this by placing stdin back into non-blocking mode after
each call to readline... I'll look into it.

Cheers,
Simon

 Please report it as a compiler bug to 
 [EMAIL PROTECTED],
 or http://sourceforge.net/projects/ghc/.
 
 
 Prelude y - catch (getChar) (x)
 
   This time I hit ^C several times, but only got a response when I
   pressed a key.
 
 iInterrupted.
 Prelude y
 ghc-5.04.1: panic! (the `impossible' happened, GHC version 5.04.1):
 rdrNameModule y
 
 Please report it as a compiler bug to 
 [EMAIL PROTECTED],
 or http://sourceforge.net/projects/ghc/.
 
 
 _
 MSN Photos is the easiest way to share and print your photos: 
 http://photos.msn.com/support/worldwide.aspx
 
 ___
 Glasgow-haskell-bugs mailing list
 [EMAIL PROTECTED]
 http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs
 
___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs



Re: ghc MacOS X 10.2 behaviour

2002-10-14 Thread Wolfgang Thaller

Simon Peyton-Jones wrote:

 [EMAIL PROTECTED] would be a better bet.
 Wolfgang Thaller is Supreme Being for MacOS so I'm cc'ing him too.

Oh, I like that title!

 | -Original Message-
 | From: [EMAIL PROTECTED] 
 [mailto:[EMAIL PROTECTED]]
 | Sent: 14 October 2002 14:44
 | To: [EMAIL PROTECTED]
 | Subject: ghc MacOS X 10.2 behaviour
 |
 | [...]
 |
 | Now, when I compile some code with ghc I get two errors:
 | /tmp/ghc617.hc:283: conflicting types for
 'GHCziTopHandler_runIO_closure'
 | and
 | /usr/local/lib/ghc-5.04/include/RtsAPI.h:125: previous declaration 
 of
 | 'GHCziTopHandler_runIO_closure'

This is an incompatibility with GCC 3.
There are two ways to work around this:
a) (the recommended way) Switch to GCC 2 using:
sudo gcc_select 2
b) Edit the file /usr/local/lib/ghc-5.04/include/RtsAPI.h. Remove the 
const from the declaration in line 125 and from the declaration next 
to it.
Compilation should now work, but the generated code is worse than with 
GCC 2.

The problem will be fixed in GHC 5.04.2 (There won't be a 5.04.1 for 
Mac OS).

 | Thanks,
 | Markus

Grüße von Graz nach München(?)!

Wolfgang Thaller

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



RE: -package-name

2002-10-14 Thread Simon Marlow


 | Aha. So how will GHC find all the various module imports?
 
 You install the package using ghc-pkg.  That tells GHC where it is.

For more information on the interaction between hierarchical libraries
and the package mechanism, see

http://www.haskell.org/pipermail/glasgow-haskell-users/2002-September/00
4005.html

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



RE: IO security

2002-10-14 Thread Simon Marlow

 I'm looking for secure compile and run-time methods to ensure 
 automatically that Haskell modules cannot perform particular 
 IO operations. Therefore, I've got some questions that might 
 be interesting for other people using GHC as well.
 
o There are functions like unsafePerformIO. How many of these
  unsafe functions exist and what are their names? Is there
  a possibility to tell GHC to reject programs in which
  such functions occur? Concerning, e.g.,  the rewrite-rule system,
  how can we prevent that these functions are applied by
  some trick, invisible by an automatic inspection of the
  source code?
  
o Is the function print secure in the sense that all stuff
  it produces is restricted to go to stdout, even if strange
  sequences of control characters appear?
 
o Is there a way to tell the GHC run-time system to block
  file operations or system calls coming from the
  application program, while permitting input/output
  via stdin/stdout?

Security of a Haskell program is an interesting research area in itself.
I suspect the folks at Galois Connections have something to say on the
topic.

My opinion would be that trying to approach the problem as you have,
namely identifying the unsafe features and removing them, is likely to
be difficult or impossible to verify.  A better approach might be to
start from a clean slate (ie. remove the IO monad altogether) and
incrementally add in safe features separately.

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



Q: Bug? 'Storable' and 'with'

2002-10-14 Thread Jan Kybic

Hi,
I am using ghc-5.04 and a code like:

with c ( \c' - hPutBuf h c' (sizeOf c))

fails with Fail: Prelude.undefined when c is a user defined type,
such as a pair:

instance (Storable at,Storable bt) = Storable (at,bt) where
 sizeOf (a,b) = sizeOf a + sizeOf b
 alignment (a,b) = max (alignment a) (alignment b)
 peek p = do a - peek ((castPtr p):: Ptr at) 
 b - peekByteOff ((castPtr p):: Ptr bt) (sizeOf a)
 return (a,b)
 poke p (a,b) = do poke ((castPtr p):: Ptr at) a
   pokeByteOff ((castPtr p):: Ptr bt) (sizeOf a) b


On the other hand, if I replace 'with' with 'with1':

with1 :: (Storable a) = a - ( Ptr a - IO b ) - IO b
with1 x f = do p - mallocBytes (sizeOf x)
   let p'=castPtr p :: Ptr a
   poke p' x
   y - f p'
   free p
   return y

it seems to work. I could not even get to work 'malloc :: IO (Ptr
(Int,Int))', while 'malloc :: IO (Ptr Int)' works fine.
Am I doing something wrong, or is there a bug in
the library code?

Yours,

Jan


-- 
-
Jan Kybic [EMAIL PROTECTED]  Odyssee, INRIA, Sophia-Antipolis, France
   or [EMAIL PROTECTED],tel. work +33 492 38 7589, fax 7845
 http://www-sop.inria.fr/odyssee/team/Jan.Kybic/index.en.html
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



ghc MacOS X 10.2 behaviour

2002-10-14 Thread Markus . Schnell

Hi all,

I'm working with Haskell on MacOS X 10.2.1 using the binaries from
www.uni-graz.at/imawww/haskell.

Now, when I compile some code with ghc I get two errors:
/tmp/ghc617.hc:283: conflicting types for 'GHCziTopHandler_runIO_closure'
and
/usr/local/lib/ghc-5.04/include/RtsAPI.h:125: previous declaration of
'GHCziTopHandler_runIO_closure'

Using ghci or compiling with -O2 doesn't show this error.

Any ideas what's wrong?

Thanks,
Markus

By the way, if there is a list more suited for the subject, please tell me.


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



RE: Bug? 'Storable' and 'with'

2002-10-14 Thread Simon Marlow

 I am using ghc-5.04 and a code like:
 
 with c ( \c' - hPutBuf h c' (sizeOf c))
 
 fails with Fail: Prelude.undefined when c is a user defined type,
 such as a pair:
 
 instance (Storable at,Storable bt) = Storable (at,bt) where
sizeOf (a,b) = sizeOf a + sizeOf b
alignment (a,b) = max (alignment a) (alignment b)
peek p = do a - peek ((castPtr p):: Ptr at) 
b - peekByteOff ((castPtr p):: Ptr bt) (sizeOf a)
return (a,b)
poke p (a,b) = do poke ((castPtr p):: Ptr at) a
  pokeByteOff ((castPtr p):: Ptr bt) 
 (sizeOf a) b

sizeOf and alignment are not supposed to evaluate their arguments.  You
might try making the definitions in your instance above a little lazier:

sizeOf z = sizeOf a + sizeOf b where (a,b) = z
alignment z = max (alignment a) (alignment b) where (a,b) = z

(feel free to use '~' if you prefer).

Cheers,
Simon

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: efficiency of mfix

2002-10-14 Thread Hal Daume III

Hi again, all.

So I rewrote some of the versions, so there are now six versions of the
array normalization code.  They are:

normal: combination of foldM and mapM_
loop:   a two-pass loop mimicking foldM and mapM_
unboxed-normal: normal on unboxed arrays
unboxed-loop:   loop on unboxed arrays
fix:using fixIO and a look with Double accumulator
cpsfix: using fixIO and a CPS accumulator

I ran each of these on arrays of size 100,000, 250,000, 500,000 and
1,000,000 elements.  The results are:

|   FIXIO|  TWO LOOPS
|  fix   cpsfix  |   map/foldloopunboxed-m/f
unboxed-loop
++--
 10 |  0.71   1.37   | 1.60  1.61   0.90  0.42  
 25 |  6.51   5.74   | 7.48  7.24   2.90  1.22  
 50 | 23.88  21.32   |25.35 26.38   7.51  2.27  
100 | 92.72  79.16   |97.83105.73  21.78  4.54  

(sorry if that wraps on your screen -- see the attached file)

So, looking at the FIXIO methods, for large arrays, cpsfix seems to
dominate.  There's a small overhead for small arrays, but this is passed
once we get to 250,000 elements (probably much before).

I'm (pleasantly) surprised that both fix and cps fix consistently beat the
two boxed implementations on the right.  I'm shocked that the handwritten
loop version does worse than the map/fold version and cannot explain this.

Yet, when looking at the unboxed arrays, the map/fold version does *much*
worse than the loop version.  I'm guessing this has to do with the fact
that in the loop version the compiler is unboxing the index variable for
the whole loop, rather than unboxing each element in the list for map/fold
one-by-one.

While I'm happy that the fix versions outperform the 2-pass versions for
boxed arrays, the discrepency between 79.16 seconds for one million
elements and 4.54 sectons on the same data is alarming.  Can anyone
suggest a way to reconcile this?

 - Hal

p.s., I've attached the code and results (as comments in the code).


--
Hal Daume III

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

On Sat, 28 Sep 2002, Levent Erkok wrote:

 On Friday 27 September 2002 05:19 pm, Hal Daume III wrote:
  There is a one pass solution using mfix.  This looks like:
 
mfix (\ ~s - ioaA a 1 s)
 
  where  ioaA is defined as:
 
ioaA a i s
 
  | i  sz = return 0
  | otherwise =
 
  do s' - ioaA a (i+1) s
 v  - readArray a i
 writeArray a i (v/s)
 return (s' + v)
  where (_,sz) = Data.Array.IO.bounds a
 
  Using unboxed arrays is not possible in the fixed point version
  (loop).  On the normal version, it just about triples the speed across the
  board.
 
 Hi,
 
 I'm not sure if it's mfix we should blame here. Can you please 
 experiment with the following version of normalize and report on 
 running times?
 
   norm a = mdo s - ioaA 1 s id
return ()
 where (_, sz) = bounds a
   ioaA i s acc
| i  sz = return (acc 0)
| True   =
do v - readArray a i
   writeArray a i (v/s)
   ioaA (i+1) s (\x - v + acc x)
 
 It'd be interesting to see the results especially for very large 
 inputs (i.e. = half a million elements.)
 
 -Levent.
 



module Main where

import Data.Array
import Data.Array.IO
import Control.Monad
import Control.Monad.Fix
import System


ioaA a s = ioaA' 1 s 0
where ioaA' i s acc
  | i  sz = return acc
  | True   = do v - readArray a i
writeArray a i (v / s)
ioaA' (i+1) s $! (v + acc)
  (_, sz) = Data.Array.IO.bounds a

ioaACPS a s = ioaACPS' 1 s id
where (_, sz) = Data.Array.IO.bounds a
  ioaACPS' i s acc
   | i  sz = return (acc 0)
   | True   =
   do v - readArray a i
  writeArray a i (v/s)
  ioaACPS' (i+1) s (\x - v + acc x)


main = do
  [method,n] - getArgs
  (a::IOArray Int Double) - newListArray (1::Int,read n) [(1::Double)..read n]
  if method == fix
then mfix (\ ~s - ioaA a s)  return ()
else if method == cps
   then mfix (\ ~s - ioaACPS a s)  return ()
   else if method == loop
  then normLoop a
  else norm a
  return ()

norm a = do
  t - foldM (\t i - (t+) `liftM` readArray a i) 0 [1..sz]
  mapM_ (\i - readArray a i = writeArray a i . (/t)) [1..sz]
  where (_,sz) = Data.Array.IO.bounds a

normLoop a = do t - normLoop' 1 0
normLoop'' 1 t
where normLoop' i acc
  | i  sz = return acc
  | True   = do v - readArray a i
 

Re: efficiency of mfix

2002-10-14 Thread Levent Erkok

On Monday 14 October 2002 09:25 am, you wrote:
 While I'm happy that the fix versions outperform the 2-pass versions for
 boxed arrays, the discrepency between 79.16 seconds for one million
 elements and 4.54 sectons on the same data is alarming.  Can anyone
 suggest a way to reconcile this?

As you've remarked before, the mfix version crucially depends on 
boxing: it wouldn't work with unboxed arrays since the sum is only 
available after the whole array is traversed. So, the question boils
down to the efficiency of boxed vs. unboxed data access, and I don't 
think there's much we can do there. Of course, I'd love to be proven 
wrong on this one..

-Levent.
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell