Order of libraries

1997-10-14 Thread Stephan Tobies

Another little problem:

When linking programs which need additional libraries (say
-lreadline -ltermcap) the ghc driver puts these after its
own libraries when calling the linker.

This is not desirable since the linker complains about unresolved
names.

Switchig the order of $UserLibrary and $SystemLibrary in the ghc driver
solves the problem, but I don't know if that is ALWAYS the right
behaviour.

Stephan
-- 
Stephan Tobies, Student of Computer Science, RWTH Aachen
  mailto:[EMAIL PROTECTED]
## There is much pleasure to be gained
   from useless knowledge - B. Russel ##



Re: Order of libraries

1997-10-14 Thread Sigbjorn Finne


Stephan Tobies writes:
 Another little problem:
 
 When linking programs which need additional libraries (say
 -lreadline -ltermcap) the ghc driver puts these after its
 own libraries when calling the linker.
 
 This is not desirable since the linker complains about unresolved
 names.

 Switchig the order of $UserLibrary and $SystemLibrary in the ghc driver
 solves the problem, but I don't know if that is ALWAYS the right
 behaviour.
 

Hi,

the present arrangement goes wrong if anything in $SystemLibrary
depends on symbols in $UserLibrary. That's not supposed to happen,
$SystemLibrary is intended to be `closed'. If that's what you're
experiencing, please let us know whatwhere this happens so we can
patch up $SystemLibrary to avoid this.

(Switching the two is likely to fail if any of the user libraries
contain ghc compiled code.)

Thx,
--Sigbjorn



Re: GranSim/parallel versions of 2.08

1997-10-14 Thread Sigbjorn Finne


Sven Panne writes:
 The normal/profiling/concurrent versions of 2.08 compiled far too
 smoothly, so I was looking for new installation challenges.   ;-)
 Alas, compiling with mg and mp added to GhcLibWays didn't work:
 
* During the compilation of the _mg-versions of the libs the
  assembler mangler complains about 5500 times. It's totally
  unclear to me what it means: bug/warning/error?   Example:
 

gcc generates code which jumps via %ecx for some reason when compiling
gransim code, something that isn't caught by the mangler. Patch appended.

 
* The parallel version of the libs can't be compiled because
  ghc/lib/glaExts/Foreign.lhs contains lots of
  #ifndef__PARALLEL_HASKELL__ lines.  Therefore, some exports
  are missing later (e.g. for PackedString).
 

To get the show on the road again here, you'll have to strategically
add #ifndef__PARALLEL_HASKELL__ to avoid referencing stuff that isn't
supported under Parallel Haskell. Sorry, haven't got a patch for this.

--Sigbjorn

*** ghc/driver/ghc-asm.lprl.~1~ Wed Aug 27 15:53:33 1997
--- ghc/driver/ghc-asm.lprl Tue Oct 14 19:40:21 1997
***
*** 976,981 
--- 976,982 
$c =~ 
s/^\s+ldil.*\n\s+ldo.*\n\s+bv.*\n(.*\n)?\s+\.EXIT/$1\t.EXIT/;
} elsif ( $TargetPlatform =~ /^i386-/ ) {
$c =~ s/^\tmovl \$${T_US}${symb}_fast\d+,\%edx\n\tjmp 
\*\%edx\n//;
+   $c =~ s/^\tmovl \$${T_US}${symb}_fast\d+,\%ecx\n\tjmp 
+\*\%ecx\n//;
$c =~ s/^\tmovl \$${T_US}${symb}_fast\d+,\%eax\n\tjmp 
\*\%eax\n//;
} elsif ( $TargetPlatform =~ /^mips-/ ) {
$c =~ s/^\tjmp \$31,\(\$27\),0\n\t\.align 4\n\t\.end/\t.align 
4\n\t.end/;



Library Random is missing with ghc-2.08 src distribution

1997-10-14 Thread Stephan Tobies

The subject says it all...
-- 
Stephan Tobies, Student of Computer Science, RWTH Aachen
  mailto:[EMAIL PROTECTED]
## There is much pleasure to be gained
   from useless knowledge - B. Russel ##



Re: ghc Diagnostics

1997-10-14 Thread Manuel Chakravarty

Simon Marlow wrote:

 I take your point that this isn't very consistent:  there should be a
 way to turn off all warnings easily.  What do other people think?
 
 The options are:
 
   * have all warnings off by default, a standard set of warnings
 being available by adding the -W command line option.
 
   * have a standard set of warnings on by default, with all
 warnings being turned off by the -Wnot (or something) flag.

I'd prefer to have the warnings off by default.  And why
don't go for a command line option set like that of the
`gcc'?  Then, `-Wall' activates all warnings and you can
get the individual warnings with `-Wwarning name'.

Manuel




Re: profiling

1997-10-14 Thread Simon L Peyton Jones


Marc

I strongly suspect that the names are simply truncated before they get
into a .hp file.  Doubtless this could be fixed.  

However, we're now embarking on building a new RTS, designed to support
both GHC and Hugs, so I'd rather just make sure that the new system doesn't 
truncate names.  (The new system will take a few months; don't hold your 
breath.)

Is this a show-stopper for you, or can you get by (perhaps by changing your
function names)?

Simon

 When I profile my sources (-auto-all) it happens
 a lot that I see names of the following form
 
  SourceFile:ModuleName/descripto
 
 in stead of names of the form
 
  SourceFile:ModuleName/descriptor_prefix_TYPE_SUFFIX
 
 as I would have expected.
 
 Is there a way to get the full function-names out of
 the profiling package? I have looked at the .hp files,
 but the information does not seem to be available at
 that level.
 
 
 Any help would be greatly appreciated.
 
 Regards,
 
 
 Marc van Dongen
 [EMAIL PROTECTED]





Re: profiling

1997-10-14 Thread Kevin Hammond

At 9:32 am 14/10/97, Simon L Peyton Jones wrote:
I strongly suspect that the names are simply truncated before they get
into a .hp file.  Doubtless this could be fixed.

Yes, I came across this when working with the parallel cost-centre code.
It would
be extremely easy to change the appropriate module in the runtime system
(runtime/profiling/CostCentres.lc -- there are some %-16s and %-11s fields
that need to be changed to achieve this as far as I can tell), and not hard
to add a
flag to do this...

I'm not sure why the restriction is there -- maybe just to tidy the output?!
It is a bit of a pain.

Regards,
Kevin

--
Division of Computer Science,   Tel: +44-1334 463241 (Direct)
School of Mathematical  Fax: +44-1334 463278
 and Computational Sciences,URL:
http://www.dcs.st-and.ac.uk/~kh/kh.html
University of St. Andrews, Fife, KY16 9SS.





Typechecking Monads

1997-10-14 Thread Ch. A. Herrmann

Hello,

in the following example, where I define a
state transformer monad "St" parametrized with 
the state "c", the ghc-2.08 typechecker reports
the following error message in the type definition of
function "foo" which uses the instantiated "St":  

  `St' should have no arguments, but has been given 1 .

It works if I comment out the type definition. It also
works in hugs-1.3 with the type definition. Is there a
way to get it being typechecked by given a special compiler option?

Thanks in advance
--
 Christoph Herrmann
 E-mail:  [EMAIL PROTECTED]
 WWW: http://brahms.fmi.uni-passau.de/cl/staff/herrmann.html
--
data State c a = State (c - (a,c))

unState :: State c a - (c - (a,c))
unState (State x) = x

unitState :: a - State c a
unitState a = State (\s0 - (a,s0))

bindState :: State c a - (a - State c b) - State c b
bindState m k = State (\s0 - let (a,s1) = (unState m) s0
  (b,s2) = (unState (k a)) s1 
  in (b,s2))

instance Eq c = Monad (State c) where
return = unitState 
(=)  = bindState 

data TS = TS { vs::Int } deriving (Show,Eq)

type St = State TS

foo :: Int - St Int  -- it works if this line is not given
foo x = return x
--
END OF MESSAGE