RE: Linking with object files

2003-01-09 Thread Simon Marlow

 On Wednesday 08 January 2003  5:00 pm, Simon Marlow wrote:
  What command line are you using?  Here's what I did:
 
  ~/scratch  cat  foo.c
  ~/scratch  gcc -c foo.c
  ~/scratch  ghc --make hello.hs foo.o
  ghc-5.04.2: chasing modules from: hello.hs
  Skipping  Main ( hello.hs, ./hello.o )
  ghc: linking ...
  ~/scratch 
 
 The exact command line I'm using is..
  ghc --make -fglasgow-exts -Wall -o Main.exe Main.hs Fill.o Render.o
 which gives..
  ghc-5.04.2: chasing modules from: Main.hs,Fill.o,Render.o
  ghc-5.04.2: can't find module `Fill.o' (while processing Fill.o)
 
 But playing about a bit, I found the solution. It doesn't like
 upper case object file names. Not sure if that's by design or an
 oversight. I've changed them to lower case and it works fine now.

Eek!  That's a bug, thanks!

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



Re: reaping fd's and flushing buffers

2003-01-09 Thread William Lee Irwin III
On Mon, Jan 06, 2003 at 02:02:13PM -, Simon Marlow wrote:
 ... actually I've just looked at the code and it looks wrong, aargh!
 The finalizer is attached to the wrong side.  If you have a source tree
 handy, try changing the following line in libraries/base/GHC/Handle.hs:
  addMVarFinalizer read_side (handleFinalizer read_side)
 to
  addMVarFinalizer write_side (handleFinalizer write_side)

On Mon, Jan 06, 2003 at 06:13:27AM -0800, William Lee Irwin III wrote:
 Thanks, I've started brewing up a tree and I'll take that for a spin
 when it's done cooking.

ouch! jadetex needs an upgrade (ghc debian maintainer?).

But OTOH this does solve my problem.


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



RE: Two Questions: 'memory consumption' and '-pgmL'

2003-01-09 Thread Simon Marlow
 first of all, let me thank you for writing and maintaining this
 excellent compiler! I am using it a lot recently and I couldn't be
 more happy with it. Thanks! :-)
 
 I wouldn't be posting here, though, if hadn't had a questions ... So
 here I go:
 
  (1) Using the DtdToHaskell tool, I converted the XML Docbook DTD to
  Haskell code. The resulting parser is amazing: It is almost 4
  megabyte large, 72800 lines of code. Now I tried to compile this
  beast and ran fresh out of memory.
 
  I fiddled with the RTS options to no avail. At some point GHC was
  consuming more than 800 megabytes of RAM, what resulted in
  serious thrashing (my machine has only 512 MB) and eventually the
  process was terminated.
 
  Does anyone have by any ideas how I could tackle this problem?
  Can I reduce GHC's memory requirements somehow? Can I split the
  module up and compile it in parts? In different phases? Anything?
  (If nothing comes up, I guess buying some more RAM is the
  answer.)

You can try fiddling with GHC's GC settings to reduce memory
consumption.  The section of the User's Guide on runtime flags has some
hints; I would try -c first (turn on the compacting collector).  Adding
more generations (eg. -G3) might help, and setting a maximum heap size
(eg. -M512m) will cause GHC to try to trim down its memory use when it
gets close to this boundary.  Remember to surround any RTS options with
+RTS ... -RTS.

  (2) According to the documentation, GHC allows for setting the
  literate pre-processor to be used when compiling an .lhs file.
  This is supposed to occur with the '-pgmL' option, but no matter
  what I try, GHC always tells me:
 
 | ghc-5.04.2: unrecognised flags: -pgmL
 | Usage: For basic information, try the `--help' option.
 
  Am I doing something wrong or is the documentation out of synch
  with the implementation?

Hmm, good point.  This option is missing from the implementation, thanks
for pointing it out.

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



jadetex (was: Re: reaping fd's and flushing buffers)

2003-01-09 Thread Michael Weber
On Thu, Jan 09, 2003 at 02:37:03AM -0800, William Lee Irwin III wrote:
 On Mon, Jan 06, 2003 at 06:13:27AM -0800, William Lee Irwin III wrote:
  Thanks, I've started brewing up a tree and I'll take that for a spin
  when it's done cooking.
 
 ouch! jadetex needs an upgrade (ghc debian maintainer?).

Probably related to this bug: http://bugs.debian.org/171985  ?

(also includes hint for workaround)


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



RE: trying to build from cvs - cc1: bad value (athlonmp) for -march= switch

2003-01-09 Thread Simon Marlow

 --
 --
 ==fptools== make all -wr;
  in /home/shae/build/haskell/fpbuild/ghc/rts
 --
 --
 ../../ghc/compiler/ghc-inplace -optc-O -optc-Wall -optc-W 
 -optc-Wstrict-prototypes -optc-Wmissing-prototypes 
 -optc-Wmissing-declarations -optc-Winline 
 -optc-Waggregate-return -optc-Wbad-function-cast 
 -optc-I../includes -optc-I. -optc-Iparallel 
 -optc-DCOMPILING_RTS -optc-O2 -optc-fomit-frame-pointer 
 -optc-mpreferred-stack-boundary=2 -optc-march=athlonmp 
 -optc-DTHREADED_RTS -H16m -O -O2 -static-c Adjustor.c -o 
 Adjustor.o
 cc1: bad value (athlonmp) for -march= switch
 cc1: bad value (athlonmp) for -mcpu= switch
 make[2]: *** [Adjustor.o] Error 1
 make[1]: *** [all] Error 1
 
 
 running gcc -v gives:
 Reading specs from /usr/lib/gcc-lib/i386-linux/3.2.2/specs
 Configured with: ../src/configure -v 
 --enable-languages=c,c++,java,f77,proto,pascal,objc,ada 
 --prefix=/usr --mandir=/usr/share/man 
 --infodir=/usr/share/info 
 --with-gxx-include-dir=/usr/include/c++/3.2 --enable-shared 
 --with-system-zlib --enable-nls --without-included-gettext 
 --enable-__cxa_atexit --enable-clocale=gnu 
 --enable-java-gc=boehm --enable-objc-gc i386-linux
 Thread model: posix
 gcc version 3.2.2 20021231 (Debian prerelease)
 
 Athlon MP is the correct arch/cpu, and gcc 3.2.2 has 
 -march=athlonmp available.
 Any ideas?

Are you sure that GHC is running the same gcc?  Try 'ghc -v -fvia-C' on
some small Haskell source file.

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



Re: readping fd's and flushing buffers

2003-01-09 Thread Keean Schupke
This may be related to the answer just given to do with finalizing the 
Handles, as I have a
problem with sockets hanging around after a host name resolution has 
failed (using the simple socket
library). Having looked at the code I would like to suggest the 
following change:

connectTo hostname (PortNumber port) = do
   proto   - getProtocolNumber tcp
   sock- socket AF_INET Stream proto
   he - getHostByName hostname
   connect sock (SockAddrInet port (hostAddress he))
   socketToHandle sock ReadWriteMode

Should become:

connectTo hostname (PortNumber port) = do
   proto   - getProtocolNumber tcp
   sock- socket AF_INET Stream proto
   (do
   he - getHostByName hostname
   connect sock (SockAddrInet port (hostAddress he))
   socketToHandle sock ReadWriteMode) `Exception.catch` (\e - do 
sClose sock;throw e)

Is this a sensible change to make?

   Regards,
   Keean Schupke.


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


RE: readping fd's and flushing buffers

2003-01-09 Thread Simon Marlow
 This may be related to the answer just given to do with 
 finalizing the 
 Handles, as I have a
 problem with sockets hanging around after a host name resolution has 
 failed (using the simple socket
 library). Having looked at the code I would like to suggest the 
 following change:
 
 connectTo hostname (PortNumber port) = do
 proto   - getProtocolNumber tcp
 sock- socket AF_INET Stream proto
 he - getHostByName hostname
 connect sock (SockAddrInet port (hostAddress he))
 socketToHandle sock ReadWriteMode
 
 Should become:
 
 connectTo hostname (PortNumber port) = do
 proto   - getProtocolNumber tcp
 sock- socket AF_INET Stream proto
 (do
 he - getHostByName hostname
 connect sock (SockAddrInet port (hostAddress he))
 socketToHandle sock ReadWriteMode) `Exception.catch` 
 (\e - do 
 sClose sock;throw e)
 
 Is this a sensible change to make?

Yes, well spotted.  I'll add the exception handler.

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



openFile and threads

2003-01-09 Thread Peter Thiemann
Folks,

here is the piece of code that takes most of the time in a program I
have:

  f6 = {-# SCC f6 #-}\gumd -
let fileName = usermetadir ++ gumd in
catch (do h - {-# SCC f6.1 #-} openFile fileName ReadMode
  str - {-# SCC f6.2 #-} hGetLine h
  _ - {-# SCC f6.2a #-} hClose h
  return $ {-# SCC f6.3 #-} words str)
  (const $ return [])

Profiling yields this output:
  individualinherited
COST CENTRE  MODULE  no.entries  %time %alloc   %time %alloc
  f6 MailStore  346 577   0.03.587.5   85.1
   f6.3  MailStore  351   0   0.09.9 0.09.9
   f6.2a MailStore  350   0   0.00.7 0.00.7
   f6.2  MailStore  349   0   0.07.5 0.07.5
   f6.1  MailStore  347   0  87.5   63.587.5   63.5

If I read this correctly, openFile performs 63.5% of all allocations
and takes 87.5% of the runtime.

Now I'm wondering about ways to cut that down:
1. How can I avoid the allocations inside of openFile?
2. Would it help to call f6 in different threads? That is, does a
   thread yield when it calls an IO function?

Any help appreciated.

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



Re: Two Questions: 'memory consumption' and '-pgmL'

2003-01-09 Thread Peter Simons
Simon Marlow writes:

  I would try -c first (turn on the compacting collector). Adding
  more generations (eg. -G3) might help, and setting a maximum heap
  size (eg. -M512m) will cause GHC to try to trim down its memory use
  when it gets close to this boundary.

Unfortunately neither of that helped. It appears that ghc simply
_needs_ that amount of memory. No matter what option I gave, at one
point it hit the 800 MB limit and aborted. (I specified -M800 because
if it used more memory than that, the machine stood basically still
with thrashing.)

Looks like I'll have to support the memor chip industry ... The
problem is that if a 512MB machine cannot compile it, I wonder how the
_users_ of my program will get along. I guess they'll tend to have
smaller machines than the average software developer does.

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



RE: readping fd's and flushing buffers

2003-01-09 Thread Keean
A related problem... connections are refused when using accept if the
hostname doesn't resolve. Maybe something like this would help, unless there
is a better way?

accept sock = do
 ~(sock', (SockAddrInet port haddr)) - Socket.accept sock
 (HostEntry peer _ _ _) - ((getHostByAddr AF_INET haddr)
`Control.Exception.catch` (\_ -
   return (HostEntry ((showHex ((haddr `shiftR` 24) .. 0xff) . showChar '.'
. showHex ((haddr `shiftR` 16) .. 0xff)
  . showChar '.' . showHex ((haddr `shiftR` 8) .. 0xff) . showChar '.'
. showHex (haddr .. 0xff)) ) [] AF_INET [])))
 handle - socketToHandle sock' ReadWriteMode
 return (handle, peer, port)

Regards,
Keean Schupke.

-Original Message-
From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED]]On Behalf Of Simon
Marlow
Sent: 09 January 2003 13:18
To: Keean Schupke; [EMAIL PROTECTED]
Subject: RE: readping fd's and flushing buffers


 This may be related to the answer just given to do with
 finalizing the
 Handles, as I have a
 problem with sockets hanging around after a host name resolution has
 failed (using the simple socket
 library). Having looked at the code I would like to suggest the
 following change:

 connectTo hostname (PortNumber port) = do
 proto   - getProtocolNumber tcp
 sock- socket AF_INET Stream proto
 he - getHostByName hostname
 connect sock (SockAddrInet port (hostAddress he))
 socketToHandle sock ReadWriteMode

 Should become:

 connectTo hostname (PortNumber port) = do
 proto   - getProtocolNumber tcp
 sock- socket AF_INET Stream proto
 (do
 he - getHostByName hostname
 connect sock (SockAddrInet port (hostAddress he))
 socketToHandle sock ReadWriteMode) `Exception.catch`
 (\e - do
 sClose sock;throw e)

 Is this a sensible change to make?

Yes, well spotted.  I'll add the exception handler.

Cheers,
Simon
___
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



building stage=2 on solaris

2003-01-09 Thread Hal Daume III
I know this is somewhat related to something in the FAQ, but I'm having a
bit of trouble building GHC from CVS source (gmake bootstrap).  Stage 1
completes find and I get a ghc-inplace as I should.  The last bit looks
like:

gmake[1]: Entering directory `/nfs/nlg/users/hdaume/ghc-cvs/ghc/compiler'
../../glafp-utils/mkdirhier/mkdirhier stage2
for i in utils basicTypes types hsSyn prelude rename typecheck deSugar
coreSyn specialise simplCore stranal stgSyn simplStg codeGen absCSyn main
profiling parser usageSP cprAnalysis compMan ndpFlatten nativeGen ghci; do
\
../../glafp-utils/mkdirhier/mkdirhier stage2/$i; \
done
for i in */*hi-boot*; do \
gln -s -f ../../$i stage2/$i; \
done
../../ghc/compiler/stage1/ghc-inplace -M -optdep-f -optdep.depend-BASE
-osuf o -I../includes   -H64m -O0 -fno-warn-unused-matches -lbfd -liberty
-iutils -ibasicTypes -itypes -ihsSyn -iprelude -irename -itypecheck
-ideSugar -icoreSyn -ispecialise -isimplCore -istranal -istgSyn -isimplStg
-icodeGen -iabsCSyn -imain -iprofiling -iparser -iusageSP -icprAnalysis
-icompMan -indpFlatten -inativeGen -ighci -DGHCI -package haskell-src
-package unix -package readline -cpp -fglasgow-exts -I. -IcodeGen
-InativeGen -Iparser -recomp -DDEBUG -H16M '-#include hschooks.h'
absCSyn/AbsCSyn.lhs absCSyn/AbsCUtils.lhs absCSyn/CLabel.lhs
absCSyn/CStrings.lhs absCSyn/Costs.lhs absCSyn/MachOp.hs
absCSyn/PprAbsC.lhs basicTypes/BasicTypes.lhs basicTypes/DataCon.lhs
basicTypes/Demand.lhs basicTypes/FieldLabel.lhs basicTypes/Id.lhs
basicTypes/IdInfo.lhs basicTypes/Literal.lhs basicTypes/MkId.lhs
basicTypes/Module.lhs basicTypes/Name.lhs basicTypes/NameEnv.lhs
basicTypes/NameSet.lhs basicTypes/NewDemand.lhs basicTypes/OccName.lhs
basicTypes/RdrName.lhs basicTypes/SrcLoc.lhs basicTypes/UniqSupply.lhs
basicTypes/Unique.lhs basicTypes/Var.lhs basicTypes/VarEnv.lhs
basicTypes/VarSet.lhs codeGen/CgBindery.lhs codeGen/CgCase.lhs
codeGen/CgClosure.lhs codeGen/CgCon.lhs codeGen/CgConTbls.lhs
codeGen/CgExpr.lhs codeGen/CgHeapery.lhs codeGen/CgLetNoEscape.lhs
codeGen/CgMonad.lhs codeGen/CgRetConv.lhs codeGen/CgStackery.lhs
codeGen/CgTailCall.lhs codeGen/CgUpdate.lhs codeGen/CgUsages.lhs
codeGen/ClosureInfo.lhs codeGen/CodeGen.lhs codeGen/SMRep.lhs
compMan/CompManager.lhs coreSyn/CoreFVs.lhs coreSyn/CoreLint.lhs
coreSyn/CorePrep.lhs coreSyn/CoreSyn.lhs coreSyn/CoreTidy.lhs
coreSyn/CoreUnfold.lhs coreSyn/CoreUtils.lhs coreSyn/ExternalCore.lhs
coreSyn/MkExternalCore.lhs coreSyn/PprCore.lhs coreSyn/PprExternalCore.lhs
coreSyn/Subst.lhs cprAnalysis/CprAnalyse.lhs deSugar/Check.lhs
deSugar/Desugar.lhs deSugar/DsBinds.lhs deSugar/DsCCall.lhs
deSugar/DsExpr.lhs deSugar/DsForeign.lhs deSugar/DsGRHSs.lhs
deSugar/DsListComp.lhs deSugar/DsMeta.hs deSugar/DsMonad.lhs
deSugar/DsUtils.lhs deSugar/Match.lhs deSugar/MatchCon.lhs
deSugar/MatchLit.lhs ghci/ByteCodeAsm.lhs ghci/ByteCodeFFI.lhs
ghci/ByteCodeGen.lhs ghci/ByteCodeInstr.lhs ghci/ByteCodeItbls.lhs
ghci/ByteCodeLink.lhs ghci/InteractiveUI.hs ghci/Linker.lhs
ghci/ObjLink.lhs hsSyn/Convert.lhs hsSyn/HsBinds.lhs hsSyn/HsCore.lhs
hsSyn/HsDecls.lhs hsSyn/HsExpr.lhs hsSyn/HsImpExp.lhs hsSyn/HsLit.lhs
hsSyn/HsPat.lhs hsSyn/HsSyn.lhs hsSyn/HsTypes.lhs main/BinIface.hs
main/CmdLineOpts.lhs main/CodeOutput.lhs main/Config.hs main/Constants.lhs
main/DriverFlags.hs main/DriverMkDepend.hs main/DriverPhases.hs
main/DriverPipeline.hs main/DriverState.hs main/DriverUtil.hs
main/ErrUtils.lhs main/Finder.lhs main/GetImports.hs main/HscMain.lhs
main/HscStats.lhs main/HscTypes.lhs main/Interpreter.hs main/Main.hs
main/MkIface.lhs main/Packages.lhs main/ParsePkgConf.hs main/SysTools.lhs
main/TidyPgm.lhs nativeGen/AbsCStixGen.lhs nativeGen/AsmCodeGen.lhs
nativeGen/AsmRegAlloc.lhs nativeGen/MachCode.lhs nativeGen/MachMisc.lhs
nativeGen/MachRegs.lhs nativeGen/PprMach.lhs nativeGen/RegAllocInfo.lhs
nativeGen/Stix.lhs nativeGen/StixMacro.lhs nativeGen/StixPrim.lhs
ndpFlatten/FlattenInfo.hs ndpFlatten/FlattenMonad.hs
ndpFlatten/Flattening.hs ndpFlatten/NDPCoreUtils.hs ndpFlatten/PArrAnal.hs
parser/Ctype.lhs parser/Lex.lhs parser/LexCore.hs parser/Parser.hs
parser/ParserCore.hs parser/ParserCoreUtils.hs parser/RdrHsSyn.lhs
prelude/ForeignCall.lhs prelude/PrelInfo.lhs prelude/PrelNames.lhs
prelude/PrelRules.lhs prelude/PrimOp.lhs prelude/PrimRep.lhs
prelude/TysPrim.lhs prelude/TysWiredIn.lhs profiling/CostCentre.lhs
profiling/SCCfinal.lhs rename/RnBinds.lhs rename/RnEnv.lhs
rename/RnExpr.lhs rename/RnHiFiles.lhs rename/RnHsSyn.lhs
rename/RnIfaces.lhs rename/RnNames.lhs rename/RnSource.lhs
rename/RnTypes.lhs simplCore/CSE.lhs simplCore/FloatIn.lhs
simplCore/FloatOut.lhs simplCore/LiberateCase.lhs simplCore/OccurAnal.lhs
simplCore/SAT.lhs simplCore/SATMonad.lhs simplCore/SetLevels.lhs
simplCore/SimplCore.lhs simplCore/SimplMonad.lhs simplCore/SimplUtils.lhs
simplCore/Simplify.lhs simplStg/SRT.lhs simplStg/SimplStg.lhs
simplStg/StgStats.lhs specialise/Rules.lhs specialise/SpecConstr.lhs
specialise/Specialise.lhs stgSyn/CoreToStg.lhs stgSyn/StgLint.lhs