RE: Backwards compatability of GHC-5.04

2002-07-24 Thread Simon Marlow


 ghc-pkg has become a lot pickier about directories and files 
 which are not 
 there (which is probably the Right Thing, except that it 
 becomes annoying when using things like pkg-config gtk+-2.0 --cflags 
 --libs).
 
 However, if I add a package that depends on, say, data to a 
 local package 
 config file, ghc-pkg does not check in the global package file if the 
 package data is installed there but says:
 
 Adding package description to local package file.
 dependency `data' doesn't exist
 
 
 Could anyone fix that?

Use the --force flag to ghc-pkg.  Yes, it's a problem that ghc-pkg
doesn't handle multiple package configuration files properly.

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



Re: Array faster than UArray Double, Was: ...speed of array types

2002-07-24 Thread Manuel M T Chakravarty

Jan Kybic [EMAIL PROTECTED] wrote,

 I have recently coded in Haskell a little program which evaluates 
 a function given as a series of matrix products. Matrices and vectors
 are represented as type X. Surprisingly, compiled with 'ghc -O2'
 (vers 5.02.2) the program runs faster with X=Array than with X=UArray Double. 
 I was quite puzzled by this result, I suppose that maybe the laziness 
 helps to avoid memory allocation or something. Is that possible?

This should only have an effect if parts of the resulting
matrices were not used to compute the final result.  Given
that the interface to H98 arrays heavily relies on lists for
generating arrays and extracting results, the list
computations can easily dominate the actual array
computations.  If that happens, it often depends on how much
deforestation[1] GHC can perform.

Cheers,
Manuel

[1] Static removal of intermediate data structures
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



hPutBufBAFull missing

2002-07-24 Thread Hal Daume III

I'm migrating my (stolen) Binary module to ghc 5.04 and it uses this
function which also seems to have disappeared...am I just not looking in
the right place?

--
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



Re: Foreign.destructArray

2002-07-24 Thread Hal Daume III

Doesn't look like it.  I looked around the full archive and the only
mention of destructArray is from Marcin's post from March 2001:

 If not, I'm going to add also destructArray and destructArray0 to
 MarshalArray, and lengthArray0 while I am at it (it was used internally
 so it makes sense to be provided separately), and document it.

Regardless, it would be nice if functions were first deprecated and then
removed.  I'm really wishing at this point that I hadn't upgraded to ghc
5.04; most of my programs no longer compile due to the library
restructuring and for every function I use that's not pure Haskell 98
(which is a fair amount, unfortunately), I've had to grep around the
imports directory to find out where it moved to.  I don't mean to point a
finger at anyone for this, but I was expecting either a smoother
transition or for the version number of GHC to change significantly.  A
minor version change should not break programs (imo).

Sorry for the tirade, but I'm pressured to get some code out soon and this
isn't helping things.

--
Hal Daume III

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

On Wed, 24 Jul 2002, Manuel M T Chakravarty wrote:

 Hal Daume III [EMAIL PROTECTED] wrote,
 
  what happened to Foreign.destructArray?  I can't seem to find it
  anywhere...
 
 Was removed.  The rational should be in the archive of
 [EMAIL PROTECTED]
 
 Cheers,
 Manuel
 

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



RE: Foreign.destructArray

2002-07-24 Thread Simon Peyton-Jones

| fair amount, unfortunately), I've had to grep around the 
| imports directory to find out where it moved to.  I don't 

I now use the Haddock index instead of grepping. 
Saves me a lot of time.

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



RE: Foreign.destructArray

2002-07-24 Thread Simon Marlow


 Regardless, it would be nice if functions were first 
 deprecated and then
 removed.  I'm really wishing at this point that I hadn't 
 upgraded to ghc
 5.04; most of my programs no longer compile due to the library
 restructuring and for every function I use that's not pure Haskell 98
 (which is a fair amount, unfortunately), I've had to grep around the
 imports directory to find out where it moved to.

Hmm, I tried quite hard not to break too much stuff in 5.04.  That's why
all the old hslibs are still there, and they still supply virtually the
same APIs that they did in 5.02.  Specifically, what broke for you?

 I don't mean to point a
 finger at anyone for this, but I was expecting either a smoother
 transition or for the version number of GHC to change 
 significantly.  A
 minor version change should not break programs (imo).

5.02-5.04 is a major version change :-)  We only promise not to break
APIs in patchlevel releases (eg. 5.04-5.04.1 won't break anything).

 Sorry for the tirade, but I'm pressured to get some code out 
 soon and this isn't helping things.

Not at all, we appreciate the feedback.  I'm surprised that you're
having so much trouble though.

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



RE: hPutBufBAFull missing

2002-07-24 Thread Simon Marlow


 I'm migrating my (stolen) Binary module to ghc 5.04 and it uses this
 function which also seems to have disappeared...am I just not 
 looking in the right place?

hPutBufBAFull was deprecated in 5.02 and it was removed in 5.04.  Use
hPutBufBA instead.

BTW, Haddock has a version of the Binary module which works with GHC
5.04.

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



Using UArray and Array

2002-07-24 Thread Ken T Takusagawa

I'm having difficulty compiling under 5.04 using both Arrays
and UArrays:

module Main  where{
import Array;
import Data.Array.Unboxed;

array_1::UArray(Int)(Int);
array_1 = (array (1,3) [(1,7),(2,8),(3,13)]);

array_2::Array(Int)(Int);
array_2 = (array (1,3) [(1,700),(2,800),(3,1300)]);

main::IO ();
main = putStrLn hi world
}

This gets me the errors
Ambiguous occurrence `array'
It could refer to either `Data.Array.Base.array',
imported from Data.Array.Unboxed at arrayfailx.hs:6
  or `GHC.Arr.array', imported from
Array at arrayfailx.hs:5

Suggestions?  (I would rather not have to fully qualify
every occurence of array, accumArray, and ! in my program.)

Ken Takusagawa


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



Re: Using UArray and Array

2002-07-24 Thread Hal Daume III

Not positive, but perhaps you could just hide things like (!), array,
etc., from Unboxed since these are class methods and Unboxed is probably
just reexporting what Array exports?  You should also probably import
Data.Array instead of just Array.

--
Hal Daume III

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

On Wed, 24 Jul 2002, Ken T Takusagawa wrote:

 I'm having difficulty compiling under 5.04 using both Arrays
 and UArrays:
 
 module Main  where{
 import Array;
 import Data.Array.Unboxed;
 
 array_1::UArray(Int)(Int);
 array_1 = (array (1,3) [(1,7),(2,8),(3,13)]);
 
 array_2::Array(Int)(Int);
 array_2 = (array (1,3) [(1,700),(2,800),(3,1300)]);
 
 main::IO ();
 main = putStrLn hi world
 }
 
 This gets me the errors
 Ambiguous occurrence `array'
 It could refer to either `Data.Array.Base.array',
 imported from Data.Array.Unboxed at arrayfailx.hs:6
 or `GHC.Arr.array', imported from
 Array at arrayfailx.hs:5
 
 Suggestions?  (I would rather not have to fully qualify
 every occurence of array, accumArray, and ! in my program.)
 
 Ken Takusagawa
 
 
 ___
 Glasgow-haskell-users mailing list
 [EMAIL PROTECTED]
 http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
 

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



Re: Using UArray and Array

2002-07-24 Thread Ross Paterson

On Wed, Jul 24, 2002 at 02:35:37PM -0400, Ken T Takusagawa wrote:
 I'm having difficulty compiling under 5.04 using both Arrays
 and UArrays:
 
 module Main  where{
 import Array;
 import Data.Array.Unboxed;
 
 [...]
 
 This gets me the errors
 Ambiguous occurrence `array'
 It could refer to either `Data.Array.Base.array',
 imported from Data.Array.Unboxed at arrayfailx.hs:6
 or `GHC.Arr.array', imported from
 Array at arrayfailx.hs:5

Short answer: just say

import Array(Array)
import Data.Array.Unboxed

Long answer:
It is a bit subtle, and maybe the docs could explain it more.
In Data.Array (which Array imports and re-exports), there is

array :: (Ix a) = (a,a) - [(a,b)] - Array a b

as required by Haskell 98.  (Actually it's imported from GHC.Arr.)
In Data.Array.IArray (imported and re-exported by Data.Array.UArray)
there is a function of the same name with the type

array :: (IArray a e, Ix i) = (i,i) - [(i, e)] - a i e

(actually imported from Data.Array.Base.)  This is a generalization of
the previous function, because there is an instance

instance IArray Array e

and similarly for (!), accum and the rest.

Data.Array.Unboxed then brings in Unboxed, with instances

instance IArray UArray Bool
IArray UArray Char
IArray UArray Int
etc.

The result of all this is that you need only Array from Data.Array,
and you can use the more general functions on both Array and UArray.
In the case of Array they are identical to the Data.Array ones.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



suggestion regarding :browse

2002-07-24 Thread Hal Daume III

if we have

import qualified Some.Long.Module.Name as N

we can do

:info N.somefunction

or

:info Some.Long.Module.Name.somefunction

and

:browse Some.Long.Module.Name

but not

:browse N

which would be really nice :P

if this could make its way into 5.04.1, that would be wonderful

--
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



Re: Docs missing?

2002-07-24 Thread Albert Lai

The doc RPM package for Red Hat 7.3 suffers the same problem as the
SuSE one.  Could someone please give a hand-holding guide so that we
can fix it ourselves?  Please?  Please?
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: Docs missing?

2002-07-24 Thread Jorge Adriano


 The doc RPM package for Red Hat 7.3 suffers the same problem as the
 SuSE one.  Could someone please give a hand-holding guide so that we
 can fix it ourselves?  Please?  Please?

It's easy ;)
Go to http://haskell.cs.yale.edu/ghc/documentation.html and in the 
downloadable/printable documentation section you'll find tar.gzs with the 
HTML files missing. Just untar/gunzip them in the appropriate dir (the on 
that contains the main index.html file)

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



Re: Foreign.destructArray

2002-07-24 Thread Manuel M T Chakravarty

Hal Daume III [EMAIL PROTECTED] wrote,

 Doesn't look like it.  I looked around the full archive and the only
 mention of destructArray is from Marcin's post from March 2001:
 
  If not, I'm going to add also destructArray and destructArray0 to
  MarshalArray, and lengthArray0 while I am at it (it was used internally
  so it makes sense to be provided separately), and document it.

See the thread started with 

  http://haskell.org/pipermail/ffi/2001-August/000406.html

It proposes to remove the destruct functions.

 Regardless, it would be nice if functions were first deprecated and then
 removed.  

Mea culpa.  I have usually deprecated dying FFI functions
first, but obviously screwed it up here.  Sorry.

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



Re: Need help

2002-07-24 Thread D. Tweed

On 23 Jul 2002, Alastair Reid wrote:

 
  You shouldn't _need_ to be in the IO monad to get random numbers
  (although if you choose to that can be a good choice). Clearly
  there's the need to initialise the generator, but if you want
  `random' random numbers (as opposed to a known sequence of random
  numbers for debugging) getting the value of time via an
  unsafePerformIO is as good as anything else. From then on, the
  pseudo-random number generator will deterministically produce what
  are hopefully `acceptably random looking' numbers.
 
 Isn't this a very dangerous practice?  It's so very, very easy to
 break referential transparency when using unsafePerformIO with
 functions known to produce observably different results each time you
 call it.  And once you do this, all kinds of nice Haskell properties
 go to hell.

I would imagine it's an incredibly dangerous practice; I've only actually
done this for top level CAFs, and I'd imagine these are probably much less
likely to be duplicated by optimisation which is why it hasn't bitten me.
In general I do get the seed in a top level IO monad wrapper.

 Safer ways would be to use the monadic operators as intended to get
 random seeds and then use implicit parameters to pass them around
 (using a mild variation of John Hughes' approach to mutable
 variables).

That sounds a good way (implicit parameters are on my `learn about at
some point list'). All I was trying to say, in my rather confused email,
is that __one__ haskell idiom for dealing with random numbers is by
passing around StdGen's, in contrast with the C idiom of `calling a random
number generator function' and that if you pass in an initial StdGen you
don't need to be within the IO monad to do processing involving random
numbers.

It wasn't clear to me whether Vincenzo's e-mail was saying that you just
needed to be in IO to generate the seed or that you need to be in IO to do
anything that involves generating random numbers __after you've got the
seed__. Since I have to admit I really dislike having monads extend beyond
the top couple of levels of a program I wanted to point out that actually
generating and using random numbers can be done outside IO.

___cheers,_dave_
www.cs.bris.ac.uk/~tweed/  |  `It's no good going home to practise
email:[EMAIL PROTECTED]  |   a Special Outdoor Song which Has To Be
work tel:(0117) 954-5250   |   Sung In The Snow' -- Winnie the Pooh


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



RE: Bug in library report

2002-07-24 Thread Simon Peyton-Jones


| As near as I can tell, the precedence of the bounds and 
| indices in an array doesn't matter at all.  Simon M's 
| suggested change to Page 24 is therefore good for 
| consistency, but doesn't appear to actually have any effect.  
| Am I missing something?

I think you are right, because the bounds are always 
a tuple, which is in parens by construction.   Similarly the
list of index value pairs is always enclosed in square
brackets.  But the consistency appeals to me.  And it
definitely matters for Ratio.

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



Re: Bug in library report

2002-07-24 Thread Koen Claessen

Malcolm Wallace wrote:

 | This has been said before, but maybe we need someone
 | to formulate a huge set of QuickCheck properties about
 | the Prelude/Libraries.  That would root out quite a
 | lot of remaining bugs relatively quickly I suspect.

This sounds like an interesting (student) project, that
would require to develop new methodologies for testing with
QuickCheck.

Alastair Reid wrote:

 | I think we'd want a modified version of quickcheck
 | which generated a file of results which were then
 | checked by an external tool.  The problem being that
 | there's a wide range of compiler bugs which can make a
 | program return 'True' without actually executing the
 | program correctly.

I do not understand what you mean here. Maybe an example
helps?

 | With that modification, I strongly agree.

I'm in!

/Koen.

--
Koen Claessen
http://www.cs.chalmers.se/~koen
Chalmers University, Gothenburg, Sweden.

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



PADL'03: Final Call (subm. deadline: July 31)

2002-07-24 Thread Dr. Gopal Gupta


  FINAL CALL FOR PAPERS!!!  

Fifth International Symposium on 
 Practical Aspects of Declarative Languages 2003
 (PADL '03) 

   http://www.research.avayalabs.com/user/wadler/padl03/

New Orleans, Louisiana, USA 
 Jan 13-14, 2003
  Co-located with POPL 2003 


oPAPER SUBMISSION DEADLINE: July 31. 

oPADL'03 proceedings will be published as Springer Verlag LNCS,

o$500 award for best/most-practical paper.
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Size özell....

2002-07-24 Thread seni

Sizler icin cok ozel býr sýte hazýrladýk http://www.pembelisex.com  Bu adreste 18 
kategoride  100 lerce galeri  binlerce resim ve video ya ulaþabilirsiniz. 

http://www.pembelisex.com




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



Re: Need help

2002-07-24 Thread Nick Name

On Wed, 24 Jul 2002 10:44:51 +0100 (BST)
D. Tweed [EMAIL PROTECTED] wrote:

 It wasn't clear to me whether Vincenzo's e-mail was saying that you
 just needed to be in IO to generate the seed or that you need to be in
 IO to do anything that involves generating random numbers __after
 you've got the seed__. Since I have to admit I really dislike having
 monads extend beyond the top couple of levels of a program I wanted to
 point out that actually generating and using random numbers can be
 done outside IO. 

Well, what I meant is that, being Haskell a lazy pure functional
language, the *right* way to use I/O and nondeterminism in general is
the IO monad. 

You can avoid it by using unsafeSomething but... it's unsafe. I like
haskell the way it is. 

If one wants to write pure code using a random number generator created
with newStdGen, which is in the IO monad, it's easy, he/she just writes
a pure function f whose argument is a random number generator. And
then the random number generator is created in the IO monad and f is
applied to it.

Vincenzo

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



still random number problem

2002-07-24 Thread Junjie Xu

Hi there,
First of all, I would say thank you very much for all who helped me during 
the past days.

Since I am a beginner , sometime I spent even several hours to solve a 
very simple problem.So, I still need your help in the future.

The problem is: 


import Random

uni ::  IO () - Float
uni  = do
 xs -  newStdGen 
 let
   m =  (head  (randoms xs) :: Float )

doubleit :: Float - Float
doubleit n = 2.0*n

main = print (doubleit uni)

The result is:


bash-2.05$ ghci
   ___ ___ _
  / _ \ /\  /\/ __(_)
 / /_\// /_/ / /  | |  GHC Interactive, version 5.02.2, for Haskell 
98.
/ /_\\/ __  / /___| |  http://www.haskell.org/ghc/
\/\/ /_/\/|_|  Type :? for help.
 
Loading package std ... linking ... done.
Prelude :cd test
Prelude :l random.ls
can't find module `random.ls'
Prelude :l random.hs
Compiling Main ( random.hs, interpreted )
random.hs:11: The last statement in a 'do' construct must be an expression
Failed, modules loaded: none.
Prelude

***

What is wrong with it? 

Thank you very much.

Kevin

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



Re: still random number problem

2002-07-24 Thread Nick Name

On Wed, 24 Jul 2002 19:13:22 +0100 (BST)
Junjie Xu [EMAIL PROTECTED] wrote:

  uni ::  IO () - Float
  uni  = do
   xs -  newStdGen 
   let
 m =  (head  (randoms xs) :: Float )

let x = expr in something

You miss the in something part... quite that simple.

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



overloaded num types, but not string types?

2002-07-24 Thread Hal Daume III

I was wondering if anyone's thought of overloading string literals in the
same way that numeric literals are overloaded.  I know that I tend to use
PackedStrings for almost everything, primarly due to the RegExp stuff and
efficiency.  This means my code is littered with unpackPS and
packString, as in

   ... if foo == packString bar ...

or

   ... if unpackPS foo == bar ...

I was wondering if someone might consider overloading Strings,
too.  Something like:

class StringLiteral s where
fromString :: String - s
toString :: s - String -- not necessary, really

then literals in haskell source could be converted from

   ... foo ...

to

   ... (fromString foo) ...

we'd have instances like

instance StringLiteral String where fromString = id
instance StringLiteral PackedString where fromString = packString
...etc...

if not something in ghc, perhaps this might find its way into drift???

 - hal

--
Hal Daume III

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

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



Re: Bug in library report

2002-07-24 Thread andy

On Wed, 24 Jul 2002, Koen Claessen wrote:

 Malcolm Wallace wrote:
 
  | This has been said before, but maybe we need someone
  | to formulate a huge set of QuickCheck properties about
  | the Prelude/Libraries.  That would root out quite a
  | lot of remaining bugs relatively quickly I suspect.

GHC already uses QuickCheck to test the Haskell 98 Array Module.

It does things like randomly permute the index-value pairs, then check
that the array is same. It also compares with a reference implementation
as provided in the Haskell report.

Andy Gill

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



Re: still random number problem

2002-07-24 Thread Hal Daume III

There are a few things wrong with this...

 uni ::  IO () - Float
 uni  = do
  xs -  newStdGen 
  let
m =  (head  (randoms xs) :: Float )

presumably, you want 'uni' to produce a random float.  in this case, it
has the wrong type; it is actually an IO action that returns a Float,
hence it's type should be:

  uni :: IO Float

furthermore, IO actions (and functions in general) need to return
something; since you're using 'do' notation, you need to have a call to
return, something like:

  uni = do xs - newStdGen
   let m = (head (randoms xs) :: Float)
   return m   -- return the head

or more simply

  uni = do xs - newStdGen
   return (head (randoms xs))

then, since do { x - f ; y x } really means f = \x - y x which is
f = y, you could write this as

  uni = newStdGen = return . head . randoms

(if that doesn't make sense, don't worry)

 doubleit :: Float - Float
 doubleit n = 2.0*n

this is fine

 main = print (doubleit uni)

here's another problem.  the type of uni is IO Float.  the type of
doubleit is Float - Float.  You can't pass an IO Float as a parameter
instead of a float.  what you need to do is perform the action uni, get
the result, pass it to doubleit and then print that, something like:

  main = do v - uni
print (doubleit v)

again, you can rewrite this:

  main = uni  print . doubleit

hope that made some sense, i gotta run

 - hal

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



Re: large binaries

2002-07-24 Thread Jon Cast

Malcolm Wallace [EMAIL PROTECTED] wrote:
Is there some reason haskell binaries have to be statically
linked?

 It would not be entirely fair to lay all the blame for large Haskell
 binaries entirely at the door of static vs. dynamic linking.

Well, considering that compiling the C binary statically linked
produces an even bigger executable:

$ gcc -static hello.c -o hello_c
$ ls -l hello_c hello_hs
-rwxrwxr-x1 jcastjcast  441624 Jul 23 20:56 hello_c
-rwxrwxr-x1 jcastjcast  157028 Jul 18 14:08 hello_hs

I think dynamic linking is fair game :)

 After all, the Haskell version is dynamically linked against exactly
 the same shared libraries as the C version, at least on my machine:

 ldd Hello (Hello.hs)
   libm.so.6 = /lib/libm.so.6 (0x40022000)
   libc.so.6 = /lib/libc.so.6 (0x40044000)
   /lib/ld-linux.so.2 = /lib/ld-linux.so.2 (0x4000)

 Of course, it is static linking against the *Haskell* runtime
 system, Prelude and Libraries that is the cause of binary bloat.
 Quite simply, lots of extra stuff is dragged in that isn't visible
 in the apparently simple source program.  For instance, I can find
 all the following symbols in the binary for hello world (compiled
 with nhc98):

 putStr, shows, showChar, showParen, showString, fromCString,
 toCString, hGetFileName, hPutChar, hPutStr, error, flip, id, init,
 length, not, putChar, putStrLn, seq, show, subtract, exitWith,
 instance Bounded Int (maxBound, minBound), instance Enum Ordering
 (succ, pred, toEnum, fromEnum, enumFrom, enumFromThen, enumFromTo,
 enumFromThenTo), instance Enum ErrNo (succ, pred, toEnum,
 fromEnum, enumFrom, enumFromThen, enumFromTo, enumFromThenTo),
 instance Monad IO (=, , return, fail), instance Eq ErrNo (==,
 /=), instance Eq Int (==, /=), instance Eq Ordering (==, /=),
 instance Num Int (+, -, *, negate, abs, signum, fromInteger),
 instance Ord Int (compare, , =, =, , max, min), instance Show
 ErrNo (show, showsPrec, showList), instance Show IOError (show,
 showsPrec, showList), instance Show Int (show, showsPrec, showList)

Well, look at the symbols I find in the statically linked C hello
world:

_Exit _GLOBAL_OFFSET_TABLE_ _IO_2_1_stderr_ _IO_2_1_stdin_
_IO_2_1_stdout_ _IO_adjust_column _IO_adjust_wcolumn _IO_cleanup
_IO_default_doallocate _IO_default_finish _IO_default_imbue
_IO_default_pbackfail _IO_default_read _IO_default_seek
_IO_default_seekoff _IO_default_seekpos _IO_default_setbuf
_IO_default_showmanyc _IO_default_stat _IO_default_sync
_IO_default_uflow _IO_default_underflow _IO_default_write
_IO_default_xsgetn _IO_default_xsputn _IO_do_write _IO_doallocbuf
_IO_fclose _IO_file_attach _IO_file_close _IO_file_close_it
_IO_file_doallocate _IO_file_finish _IO_file_fopen _IO_file_init
_IO_file_jumps _IO_file_open _IO_file_overflow _IO_file_read
_IO_file_seek _IO_file_seekoff _IO_file_setbuf _IO_file_stat
_IO_file_sync _IO_file_underflow _IO_file_write _IO_file_xsgetn
_IO_file_xsputn _IO_flockfile _IO_flush_all _IO_flush_all_linebuffered
_IO_flush_all_lockp _IO_fopen _IO_fprintf _IO_free_backup_area
_IO_free_wbackup_area _IO_ftrylockfile _IO_funlockfile _IO_fwide
_IO_getdelim _IO_getline _IO_getline_info _IO_helper_jumps
_IO_helper_overflow _IO_init _IO_init_marker _IO_init_wmarker
_IO_iter_begin _IO_iter_end _IO_iter_file _IO_iter_next
_IO_least_marker _IO_least_wmarker _IO_link_in _IO_list_all
_IO_list_all_stamp _IO_list_lock _IO_list_resetlock _IO_list_unlock
_IO_marker_delta _IO_marker_difference _IO_new_do_write _IO_new_fclose
_IO_new_file_attach _IO_new_file_close_it _IO_new_file_finish
_IO_new_file_fopen _IO_new_file_init _IO_new_file_overflow
_IO_new_file_seekoff _IO_new_file_setbuf _IO_new_file_sync
_IO_new_file_underflow _IO_new_file_write _IO_new_file_xsputn
_IO_new_fopen _IO_no_init _IO_padn _IO_printf _IO_remove_marker
_IO_seekmark _IO_seekoff _IO_seekwmark _IO_setb _IO_sgetn
_IO_sputbackc _IO_sputbackwc _IO_sscanf _IO_stderr _IO_stdfile_0_lock
_IO_stdfile_1_lock _IO_stdfile_2_lock _IO_stdin _IO_stdin_used
_IO_stdout _IO_str_count _IO_str_finish _IO_str_init_readonly
_IO_str_init_static _IO_str_jumps _IO_str_overflow _IO_str_pbackfail
_IO_str_seekoff _IO_str_underflow _IO_sungetc _IO_sungetwc
_IO_switch_to_backup_area _IO_switch_to_get_mode
_IO_switch_to_main_get_area _IO_switch_to_main_wget_area
_IO_switch_to_wbackup_area _IO_switch_to_wget_mode _IO_un_link
_IO_unsave_markers _IO_unsave_wmarkers _IO_vfprintf _IO_vfscanf
_IO_vsscanf _IO_wdefault_doallocate _IO_wdefault_finish
_IO_wdefault_pbackfail _IO_wdefault_setbuf _IO_wdefault_uflow
_IO_wdefault_xsgetn _IO_wdefault_xsputn _IO_wdo_write _IO_wdoallocbuf
_IO_wfile_doallocate _IO_wfile_jumps _IO_wfile_overflow
_IO_wfile_seekoff _IO_wfile_setbuf _IO_wfile_sync _IO_wfile_underflow
_IO_wfile_xsputn _IO_wide_data_0 _IO_wide_data_1 _IO_wide_data_2
_IO_wmarker_delta _IO_wpadn _IO_wsetb __CTOR_END__ __CTOR_LIST__
__DTOR_END__ __DTOR_LIST__ __EH_FRAME_BEGIN__ 

Size özell....

2002-07-24 Thread seni

Sizler icin cok ozel býr sýte hazýrladýk http://www.pembelisex.com  Bu adreste 18 
kategoride  100 lerce galeri  binlerce resim ve video ya ulaþabilirsiniz. 

http://www.pembelisex.com




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