Re: Optimization beyond the Module Border

2008-03-19 Thread Malcolm Wallace
 I'd be interested in any progress here -- we noticed issues with
 optimisations in the stream fusion package across module boundaries
 that we never tracked down. If there's some key things not firing,
 that would be good to know.

I suspect that if all modules are compiled -O0, then you recompile one
module with -O2, high up in the dependency graph (i.e. it depends on
many lower-level modules), plus all things that in turn depend on it
(--make), you will not get the good performance you expect.  None of the
lower-level functions will have exported inlinings or fusion rules into
the interface file.  _All_ modules must be recompiled with -O2,
especially the bottom of the dependency chain, to get the best benefit
from optimisation.

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: git and sync-all: Why not merge in libraries?

2008-08-07 Thread Malcolm Wallace

With the upcoming switchover to git, has any thought gone into merging
in the libraries into the main ghc tree


The libraries are going to remain under darcs, because they are shared  
with other haskell compilers.


Regards,
Malcolm

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Version control systems

2008-08-12 Thread Malcolm Wallace


On 12 Aug 2008, at 01:35, Manuel M T Chakravarty wrote:
Ah, good point!  Changing ghc to git means *all* developers of boot  
libraries need to use git *regardless* of what repo format the boot  
libraries are in.  After all, they need to validate against the  
current ghc head before pushing.


It is worth pointing out that I *never* validate against ghc head when  
I commit to the core libraries. (Actually, I don't even keep any  
checkout of ghc head.)  Generally I'm fixing something that has  
unintentionally broken the nhc98 build of the libraries, *despite* the  
breaking-patch being validated against ghc.  To be honest I don't  
particularly care if my fixing patch then breaks ghc again.  Why not?   
Because the chain of blame effectively leads back past me to the  
earlier patch.  (In practice, re-breaking ghc is very rare.)


Now, there is only one person taking care of nhc98 (me), and probably  
I'm its only user as well, but I do still think it is worth the 30  
secs or so every day it takes to check the nightly build logs and the  
30mins it occasionally takes to fix breakage when necessary.  Building  
a full Haskell'98 compiler is a significant undertaking, and it would  
be a great shame to simply discard it because the libraries are no  
longer available in a shared format.  Who knows, maybe someone will  
find it easier to port to their iPhone than ghc.  :-)


What I'm not really prepared to do is to extend the fixing time by an  
extra 30mins just to validate against ghc.  I might be prepared to  
learn a new VCS, but from what I've seen so far, git looks rather  
complex and difficult to use.


It is also worth noting that where a larger community of developers  
has gathered around a core library (e.g. Cabal), ghc has found it  
necessary to branch off a ghc-only version of that library, so that  
commits to the library head do not need to be validated against ghc  
head.  Igloo takes care of merging across a large bunch of patches  
every once in a while.  This model seems to work well.  In theory, the  
core library head could remain in darcs, with the ghc branch of it in  
git.  All the pain of merging would be dumped on one person (sorry  
Igloo!) but everyone else gets the benefit.


Regards,
Malcolm

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Version control systems

2008-08-13 Thread Malcolm Wallace

Manuel wrote:

| It is worth pointing out that I *never* validate against ghc head  
when

| I commit to the core libraries.


Sorry, but I think the only reason its halfway acceptable is that  
Malcolm didn't break the GHC build yet.  If he does, I'll be  
screaming as loudly as for anybody else.


Whilst I'm in no way saying that a working nhc98 head is anything like  
as important as a working ghc head, are you saying that I should  
scream louder everytime someone breaks nhc98 too?  It is happening  
several times a week at the moment.  It can be jolly frustrating when  
I have other things I could be doing.  But I accept that it is simply  
the price to pay for keeping up-to-date with the libraries everyone  
else is using.  Ghc has no monopoly on the core libraries.  They are  
a shared resource.


to be honest, I don't think its a valid reason for us to go to the  
trouble of having two vcs for ghc.


Well indeed, I don't want to stand in the way of ghc.  There are far  
more people contributing to it, so their needs have greater weight.   
But I am raising the libraries question, because I think it has an  
impact much more widely than just ghc (or Hugs or nhc98, for that  
matter).


Git may turn out to be sufficiently easy to use that this will all  
seem like a storm in a teacup once the dust has settled.  (I'm not  
filled with confidence by blog postings that say granted, git is a  
usability disaster zone, and [you] may find git to be hostile,  
unfriendly and needlessly complex, but those seem to be minority  
opinions.)


Regards,
Malcolm


Regards,
Malcolm

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Version control systems

2008-08-13 Thread Malcolm Wallace
 I don't think that is the right policy.  Everybody (including Malcolm)
 should validate.
 
 If you contribute code to the linux kernel, comprehensive testing of  
 the code is a requirement, too.

The analogy is flawed.  It is like asking the developers of _gcc_ to
ensure that the Linux kernel still builds after every modification to
the gcc project code base.  The projects are different, so the
suggested requirement would be an unreasonable burden.

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Version control systems

2008-08-13 Thread Malcolm Wallace
 I think an even better analogy is probably comparing it to developer
 of GCC changing the libc implementation of another compiler or vice
 versa.

Our shared libraries do not belong to any one compiler.  They are joint
creations, with a lot of community (non-compiler-hacker) involvement.

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Build system idea

2008-08-27 Thread Malcolm Wallace
John Meacham [EMAIL PROTECTED] wrote:

  (bring back hmake! :) ).

It never went away...
http://www.cs.york.ac.uk/fp/hmake

I even have the idea to allow hmake to read the .cabal file format for
configuration data (although that is waiting for a delivery of round
tuits).

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Unicode's greek lambda

2008-11-18 Thread Malcolm Wallace
 When the -XUnicodeSyntax option is specified, GHC accepts some Unicode
 characters including left/right arrows. Unfortunately, the letter
 greek lambda cannot be used. Are there any technical reasons to not
 accept it?

The greek lambda is a normal lower-case alphabetic character - it can
be used in identifier names.

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GHC 6.10.1 type puzzler

2008-11-19 Thread Malcolm Wallace
  test2 :: Box a - a - [a]
  test2 box x = go x
   where
  --  go :: a - [a]
 go y = [(val box), y]
 
  Couldn't match expected type `a1' against inferred type `a'

You need to turn on {-# ScopedTypedVariables #-}.
See

http://www.haskell.org/ghc/docs/latest/html/users_guide/other-type-extensions.html#scoped-type-variables

Your first example works without this extension, because the local
definition 'go' is fully polymorphic.  However, in the second example,
the type variable 'a' in the signature of 'go' is not fully polymorphic
- it must be exactly the _same_ 'a' as in the top-level signature.

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Can't compile GHC 6.8.2

2008-11-25 Thread Malcolm Wallace

The suggested remedy of commenting out the
line reading SRC_HC_OPTS += -fvia-C in the Makefile won't work, as
that line isn't there anyway.


In case it is not obvious from what other people have said, way back  
in the days of ghc-6.2, you got -fvia-C by default, whether it was  
specified on the command-line or not.  To override via-C, you needed  
to explicitly choose the opposite (-fasm).  With more recent versions  
of the compiler, the default flipped over to -fasm.


Regards,
Malcolm

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Re[2]: ghci and ghc -threaded broken with pipes forking

2008-12-10 Thread Malcolm Wallace
  Had you deprecated the non-threaded RTS, we would probably have no
  problems described in ticket #2848 :-/
 
  I think you'll have to deprecate it anyway, because it will be more
  and more difficult to maintain two versions of code,
 
 we may conduct small survey on amount of usage of old RTS (i mean ask
 this in haskell-cafe)

For the only application I tried, using the threaded RTS imposes a 100%
performance penalty - i.e. computation time doubles, compared to the
non-threaded RTS.  This was with ghc-6.8.2, and maybe the overhead has
improved since then?

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: IMCROSS and ghc

2008-12-11 Thread Malcolm Wallace
 basically, IMCROSS installs a couple new gccs with names like
 /usr/local/bin/i386-mingw-gcc and so forth, is there some way to get
 ghc to use said non-native compiler as its back end?

I don't know about IMCROSS specifically, but earlier this year Sylvain
Nahas adapted the build system of nhc98 to allow it to become a
cross-compiler.  At configure time, you simply give some additional
arguments to point to the C cross-compilation toolchain, e.g.

./configure --target=i386-mingw
--hostcc=i386-mingw-gcc
--hoststrip=...
--endian=-DLOW_BYTE_FIRST
--ccoption=...
--ldoption=...

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: ghci and ghc -threaded [slowdown]

2008-12-12 Thread Malcolm Wallace
Simon Marlow marlo...@gmail.com wrote:

 Malcolm Wallace wrote:
  
  For the only application I tried, using the threaded RTS imposes a
  100% performance penalty - i.e. computation time doubles, compared
  to the non-threaded RTS.  This was with ghc-6.8.2, and maybe the
  overhead has improved since then?
 
 This is a guess, but I wonder if this program is concurrent, and does
 a  lot of communication between the main thread and other threads? 

Exactly so - it hits the worst case behaviour.  This was a naive attempt
to parallelise an algorithm by shifting some work onto a spare
processor.  Unfortunately, there is a lot of communication to the main
thread, because the work that was shifted elsewhere computes a large
data structure in chunks, and passes those chunks back.  The main thread
then runs OpenGL calls using this data -- and I believe OpenGL calls must
run in a bound thread.

This all suggests that one consequence of ghc's RTS implementation
choices is that it will never be cheap to compute visualization data in
parallel with rendering it in OpenGL.  That would be a shame.  This was
exactly the parallelism I was hoping for.

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: ghci and ghc -threaded [slowdown]

2008-12-15 Thread Malcolm Wallace
 It seems that the problem you have is that moving to the multithreaded
 runtime imposes an overhead on the communication between your two
 threads,  when run on a *single CPU*.  But performance on a single CPU
 is not what  you're interested in - you said you wanted parallelism,
 and for that you  need multiple CPUs, and hence multiple OS threads.

Well, I'm interested in getting an absolute speedup.  If the threaded
performance on a single core is slightly slower than the non-threaded
performance on a single core, that would be OK provided that the
threaded performance using multiple cores was better than the same
non-threaded baseline.

However, it doesn't seem to work like that at all.  In fact, threaded on
multiple cores was _even_slower_ than threaded on a single core!

Here are some figures:

ghc-6.8.2 -O2  
 apply   MVarstrict  thr-N2  thr-N1
silicium  7.307.95 7.23   15.25  14.71
neghip4.254.43 4.186.67   6.48
hydrogen 11.75   10.8210.99   13.45  12.96
lobster  55.851.5 57.676.6   74.5

The first three columns are variations of the program using slightly
different communications mechanisms, including threads/MVars with the
non-threaded RTS.  The final two columns are for the MVar mechanism
with threaded RTS and either 1 or 2 cores.  -N2 is slowest.

 I suspect the underlying problem in your program is that the
 communication  is synchronous.  To get good parallelism you'll need to
 use asynchronous  communication, otherwise even on multiple CPUs
 you'll see little  parallelism.

I tried using Chans instead of MVars, to provide for different speeds of
reader/writer, but the timings were even worse.  (Add another 15-100%.)

When I have time to look at this again (probably in the New Year), I
will try some other strategies for communication that vary in their
synchronous/asynchronous chunk size, to see if I can pin things down
more closely.

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Type signature inside an instance declaration

2008-12-16 Thread Malcolm Wallace
Kwanghoon Choi lazysw...@gmail.com wrote:

 =
 instance Arg a = Arg [a] where
   pr _ = [ ++ pr (undefined :: a) ++ ]
 =

You want to use `asTypeOf`, with a lazy pattern to name a value of type 'a'.

pr xs = [ ++ pr (undefined `asTypeOf` x) ++ ]
where (x:_) = xs

or
pr ~(x:_) = [ ++ pr (undefined `asTypeOf` x) ++ ]

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: hsc2hs and HsFFI.h

2009-02-11 Thread Malcolm Wallace
 Currently, hsc2hs (as shipped with GHC) cannot be used with just
 hsc2hs Foo.hsc
 as it cannot find HsFFI.h

The hsc2hs repo includes a shell script (yes, I know, no good on Windows)
called hsc2hs.wrapper that already adds some default arguments.
(nhc98 has a modified version of the script, adding a -I$(includedir))

 Another option would be for the user to tell hsc2hs which compiler
 they're using, e.g.
 hsc2hs --compiler=/usr/bin/ghc Foo.hsc

On my system, hsc2hs is already installed as hsc2hs-ghc, in addition to
the plain hsc2hs, so if I want the compiler-specific tool, I can use it
directly.  (nhc98 should do the same thing, i.e. install hsc2hs-nhc98,
but I believe for historical reasons, it simply avoids installing hsc2hs
at all, to avoid conflicts with the ghc one.)

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


bug in ghc specialiser?

2009-02-11 Thread Malcolm Wallace
Here is an apparent bug in ghc's specialisation rules.  The rewrite rule
generated by a SPECIALISE pragma seems to want to pattern-match on exact
dictionaries (as well as types).  But the compiler is not necessarily
able to fully resolve dictionaries before the rules are supposed to
fire.

First, the source code we want to specialise:

{-# SPECIALISE
hedgehog :: Float - Vector3 Float
  - [Cell_8 (Coord3 Float)]
  - [Cell_8 (Vector3 Float)]
  - [(Coord3 Float, Coord3 Float)]
  #-}
hedgehog  :: ( Fractional a, Cell cell vert, Eq vert
 , Geom coord, Geom vector, Embed vector coord ) =
 a - vector a
   - [cell (coord a)]
   - [cell (vector a)]
   - [(coord a, coord a)]

And the core + interface generated for this module contains the rule:

SPEC Hedgehog.hedgehog ALWAYS forall
  Hedgehog.hedgehog @ GHC.Float.Float
@ RectGrid.Cell_8
@ CellTypes.MyVertex
@ Geometries.Coord3
@ Graphics.Rendering.OpenGL.GL.CoordTrans.Vector3
GHC.Float.$f16
RectGrid.$f2
CellTypes.$f1
Geometries.$f5
Geometries.$f3
Geometries.$f1
  = Hedgehog.hedgehog1

But in a different module, here is what the usage site looks like just
before the specialisation rules are supposed to fire:

hedgehog_a4wy =
  Hedgehog.hedgehog
@ GHC.Float.Float
@ RectGrid.Cell_8
@ CellTypes.MyVertex
@ Geometries.Coord3
@ Graphics.Rendering.OpenGL.GL.CoordTrans.Vector3
$dFractional_a4xP
RectGrid.$f2
CellTypes.$f1
(Dataset.$p2Embed
   @ Graphics.Rendering.OpenGL.GL.CoordTrans.Vector3
   @ Geometries.Coord3
   Geometries.$f1)
(Dataset.$p1Embed
   @ Graphics.Rendering.OpenGL.GL.CoordTrans.Vector3
   @ Geometries.Coord3
   Geometries.$f1)
Geometries.$f1

Notice how there are several dictionary selector functions sitting
there, so although some of the dictionaries match, not all do, and the
rule does not fire.  However, later the worker-wrapper transformation
is able to resolve those outstanding dictionaries, giving:

hedgehog_a4wy =
  Hedgehog.$whedgehog
@ GHC.Float.Float
@ RectGrid.Cell_8
@ CellTypes.MyVertex
@ Geometries.Coord3
@ Graphics.Rendering.OpenGL.GL.CoordTrans.Vector3
GHC.Float.$f16
RectGrid.$f2
Geometries.$f5
Geometries.$f3
Geometries.$f1

So I'm left calling the worker for the polymorphic version of the
function, rather than the specialised monomorphic code I wanted.  Given
how many dictionaries are involved, and that this is the inner loop of
the program, I'm hoping there is a big performance win waiting for me,
if only I can get that specialised code to run!

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: ./T and ./T log

2009-02-24 Thread Malcolm Wallace
Simon Marlow marlo...@gmail.com wrote:

 stdout should be flushed when the program exits, regardless of whether
 it  exits as a result of a clean exit or an exception.  I've just
 checked the  code, and that's certainly what is supposed to happen. 
 If anyone has  evidence to the contrary, please submit a bug report!

I believe flushing of file handles on program exit is handled by
finalizers attached to the handle.  Until recently, ghc did not
guarantee that any finalizer would ever run.

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: how dynamic stack approximation works

2009-02-24 Thread Malcolm Wallace
Peter Hercek pher...@gmail.com wrote:

  http://hackage.haskell.org/trac/ghc/wiki/ExplicitCallStack
 
 I was writing about a way how to maintain the stack as described in 
 point 6 of the page (provided that point is about dynamic stack).

The whole page (including point 6) is about explicitly maintaining a
(simulated) lexical call stack, not the dynamic one.

 As I already said in other emails, I would rather choose dynamic stack
 over lexical one if I was forced to choose only one of them. Actually,
 I  almost do not care about lexical stack and still do not understand
 why  people want it.

In a lazy language, the dynamic stack rarely tells you anything of
interest for debugging.  For the value at the top of the stack, you get
one of many possible _demand_ chains, rather than the creation chain.
The demanding location is pretty-much guaranteed not to be the site of
the bug.

But you can think of the lexical call stack as what _would_ have been
the dynamic call stack, if only the language were completely strict
rather than lazy.  Most people find the latter notion more intuitive for
the purposes of finding program errors.

 Sure, but the plan to maintain an approximate debugging dynamic stack 
 depends on one thing:

There is no need to approximate the dynamic stack.  It is directly
available to the RTS, in full detail.

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Int vs Word performance?

2009-02-27 Thread Malcolm Wallace
Claus Reinke claus.rei...@talk21.com wrote:

 A while ago, I needed lots of fairly small positive numbers,
 together with a small number of flags for each, so I thought
 I'd switch from Int to Word, and map the flags to bits.

Since there are few guarantees about the size of a Word (or Int), surely
it would be better to choose a definitely sized basic type, e.g. Word8
or Word16?  I vaguely recall that ghc used to generate better code for
definitely sized WordN than the generic unguaranteed-size Word.

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Under OS X 10.5.6: GHC 6.10.1 Release Candidate 1

2009-03-27 Thread Malcolm Wallace
Max Bolingbroke batterseapo...@hotmail.com wrote:

 2009/3/27 Simon Marlow marlo...@gmail.com:
  I have a fix for num012 (the test is broken), but I still don't know
  what's going on with num009.
 
 num009 has been broken on OS X for as long as I can remember :-).

If it is any help, I can confirm that num009 works correctly on a
PowerPC Mac with both ghc-6.8.2 and 6.10.1, but it fails on an Intel Mac
at least as far back as ghc-6.8.3.

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Proposal: Deprecate ExistentialQuantification

2009-06-27 Thread Malcolm Wallace

I would hereby like to propose that the
ExistentialQuantification extension is deprecated.


It is worth pointing out that all current Haskell implementations (to  
my knowledge) have ExistentialQuantification, whilst there is only one  
Haskell implementation that has the proposed replacement feature, GADTs.


Of course, that in itself is not an argument to avoid desirable change  
to the language, but it is one factor to consider.


Regards,
Malcolm

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: How to save a haskell data structure in C?

2009-07-03 Thread Malcolm Wallace


In C code, I want to save a complex data strcuture defined in  
haskell and pass it back to a haskell function at certain time.


Look up StablePtr in Haskell's FFI spec.

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Data.List permutations

2009-08-04 Thread Malcolm Wallace

Your function is not equivalent:

perm _|_ = _|_

permutations _|_ = _|_ : _|_


I have a vague memory that the library version diagonalises properly,  
so that if you give it a lazy infinite input, it still generates  
sensible output lazily.  If so, this important property should be  
noted in the haddocks.


Regards,
Malcolm

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: What is the mutator?

2009-08-06 Thread Malcolm Wallace
i'm not an expert, but:  once value of thunk is evaluated, it's  
written

back by code called mutator


Whilst that is indeed mutation, it is not what is usually referred to  
as the mutator in the context of garbage collection.  Quite simply,  
the mutator is the actual running program, as opposed to the GC,  
which is part of the underlying runtime system.  Conceptually, the  
mutator and GC are the two mutually-exclusive threads of control that  
modify the heap.  Usually one must halt while the other runs.


Regards,
Malcolm

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: What is the mutator?

2009-08-07 Thread Malcolm Wallace

 Say you are
 implementing a network server, for example -- you don't want
 to have big spikes in the request latency due to GC.

   We think
   concurrent GC is unlikely to be practical in the Haskell
   setting, due to the extra synchronisation needed in the
   mutator.
-- Simon Marlow


It is perfectly possible to do real-time concurrent garbage collection  
for Haskell, in an incremental fashion that guarantees a small maximum  
bound on each packet of GC work.  The tradeoff is that the percentage  
of time devoted to GC in total is much greater, and the mutator must  
do more work to co-operate with the GC.  In other words, the program  
runs slower.  This tradeoff is the same for all real-time garbage  
collection schemes as far as I am aware, in any language - either you  
can have responsiveness, or you can have better overall application  
speed, but you cannot have both.



 So I wonder, to what degree is GC latency controllable in
 Haskell? It seems that, pending further research, we can not
 hope for concurrent GC.


There have been several papers on real-time GC in Haskell (including  
one of my own).  There is no technical problem, only performance  
worries.  This is what I think Simon means by unlikely to be  
practical.


Regards,
Malcolm

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


-package-name flag in 6.10.x

2009-11-24 Thread Malcolm Wallace

The ghc documentation at
http://www.haskell.org/ghc/docs/latest/html/users_guide/packages.html
says the following:

-package-name foo
 Tells GHC the the module being compiled forms part of package  
foo.  If this flag is omitted (a very common case) then the default  
package main is assumed.


 Note: the argument to -package-name should be the full package  
identifier for the package, that is it should include the version  
number. For example: -package mypkg-1.2.


I observe that the example uses -package rather than -package-name,  
and wonder if this is a mistake.  Moreover, when I attempt to use the  
flag, like so:


$ ghc -package-name hat-2.06 ...
command line: cannot parse 'hat-2.06' as a package identifier

This used to work with ghc-6.6.x and ghc-6.8.x, but seems to have  
stopped working with ghc-6.10.x.  I surmise that the leading zero  
after the version point separator is to blame?  It seems an  
unfortunate regression.


Regards,
Malcolm

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: ANNOUNCE: GHC version 6.12.1

2009-12-14 Thread Malcolm Wallace
I've the 6.10.4 version installed on my MacOS X 10.6 OS. Have I to  
uninstall this version of GHC before installing the Mac .pkg for the  
6.12.1?


Most installer packages (_except_ for MacOS) allow you to have  
multiple previous versions of ghc - they are simply left in place (but  
must now be accessed as e.g. ghc-6.10.4 rather than plan ghc, which  
now points to the new version).


However, there is an unfortunate feature/bug of the MacOS installer  
packages that they forceably delete any previous versions of ghc that  
you had on your machine.  This is undesirable for many reasons, but as  
far as I know, it has not yet been fixed.


Regards,
Malcolm

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Where did the GHC API go?

2009-12-28 Thread Malcolm Wallace

Too late. We had a stable link, I used it, Google used it, blog posts
were written that linked to it, I've emailed my wife links to it, I've
put them in Word documents, I've posted them on internal intranets.
You can't create a link, put content behind it, then move the content
- it just breaks the whole web.


And incidentally, the _ghc_docs_ themselves continue to use these  
stable links to library docs, most of which are currently broken.


All of the following links from documentation for ghc-6.12.1 give a  
404 Not Found.  (I do not claim the list is exhaustive.)


from http://www.haskell.org/ghc/docs/latest/html/users_guide/packages.html
section 4.8 links to

http://www.haskell.org/ghc/docs/latest/html/libraries/Cabal/Distribution-Simple.html
section 4.8.8 links to
http://www.haskell.org/ghc/docs/latest/html/libraries/Cabal/Distribution-InstalledPackageInfo.html# 
%tInstalledPackageInfo
http://www.haskell.org/ghc/docs/latest/html/libraries/Cabal/Distribution-License.html#t 
:License


from 
http://www.haskell.org/ghc/docs/latest/html/users_guide/using-concurrent.html
section 4.12 links to

http://www.haskell.org/ghc/docs/latest/html/libraries/base/Control-Concurrent.html

from http://www.haskell.org/ghc/docs/latest/html/users_guide/primitives.html
section 7.2 links to
http://www.haskell.org/ghc/docs/latest/html/libraries/ghc-prim/GHC-Prim.html

from http://www.haskell.org/ghc/docs/latest/html/users_guide/syntax-extns.html
section 7.3.10 links to
http://www.haskell.org/ghc/docs/latest/html/libraries/base/GHC-Exts.html

from http://www.haskell.org/ghc/docs/latest/html/users_guide/arrow-notation.html
section 7.10 links twice to

http://www.haskell.org/ghc/docs/latest/html/libraries/base/Control-Arrow.html

from http://www.haskell.org/ghc/docs/latest/html/users_guide/pragmas.html
section 7.13.1 links to

http://www.haskell.org/ghc/docs/latest/html/libraries/Cabal/Language-Haskell-Extension.html

from http://www.haskell.org/ghc/docs/latest/html/users_guide/special-ids.html
section 7.15 links to
http://www.haskell.org/ghc/docs/latest/html/libraries/ghc-prim/GHC-Prim.html

from http://www.haskell.org/ghc/docs/latest/html/users_guide/lang-parallel.html
section 7.18.1 links to

http://www.haskell.org/ghc/docs/latest/html/libraries/base/Control-Concurrent.html
section 7.18.2 links to

http://www.haskell.org/ghc/docs/latest/html/libraries/stm/Control-Concurrent-STM.html
section 7.18.4 links to

http://www.haskell.org/ghc/docs/latest/html/libraries/parallel/Control-Parallel.html

http://www.haskell.org/ghc/docs/latest/html/libraries/parallel/Control-Parallel-Strategies.html

from http://www.haskell.org/ghc/docs/latest/html/users_guide/ffi.html
section 8 incorrectly links to

http://www.haskell.org/ghc/docs/latest/html/libraries/base/Control-Concurrent.html
where the real link ought to be
http://www.haskell.org/ghc/docs/latest/html/libraries/base/Foreign.html

from http://www.haskell.org/ghc/docs/latest/html/users_guide/ffi-ghc.html
section 8.2.4.2 links to

http://www.haskell.org/ghc/docs/latest/html/libraries/base/Control-Concurrent.html

from http://www.haskell.org/ghc/docs/latest/html/users_guide/ghci-windows.html
section 11.2 links to

http://www.haskell.org/ghc/docs/latest/html/libraries/base/GHC-ConsoleHandler.html


Regards,
Malcolm

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Qualified names in import lists

2009-12-28 Thread Malcolm Wallace

 module Main where
 import Foo (Bar.bar)

GHC apparently accepts this code, but I can find no mention of such a
feature in the GHC docs.


It certainly is an extension beyond Haskell'98 and Haskell 2010, which  
do not permit qualified names in import lists.  I cannot think for any  
use for such a feature, never mind a good one.


If ghc really does accept the example given, I would like to know what  
entity Bar.bar refers to, since it cannot possibly be exported by Foo.


Regards,
Malcolm

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Poll: Error message spans

2010-01-07 Thread Malcolm Wallace

Would you find the extra information useful, or just noise?
i.e. should we show error spans by default?


I certainly wouldn't find it distracting, and I think it could be
quite useful in many cases. I vote for turning it on by default.


I agree.


+1.

It is a feature I have always found useful in other tools.  (Although  
ghc does usually quote the entire literal source expression denoted by  
the span, so perhaps the info is slightly redundant.)


Regards,
Malcolm

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Language extensions - backwards compatibility

2010-01-29 Thread Malcolm Wallace
The flag -P for traditional gnu cpp (or --noline for stand-alone  
cpphs) should suppress the initial #line noise.


Does ghc still fail to recognise a module-start pragma, even if the  
only characters preceding it are whitespace?


I intended to give an example.

 file foo.h 
#if __GLASGOW_HASKELL__ == 604
#define PRAGMA(foo) {-# OPTIONS_GHC -X foo #-}
#else
#define PRAGMA(foo) {-# LANGUAGE foo #-}

 file Bar.hs 
#include foo.h
PRAGMA(MyLanguageOption)
module Bar where

 result 
$ ghc-6.8.2 -E -cpp -optP-P Bar.hs
$ cat Bar.hspp
{-# LINE 1 Bar.hs #-}



{-# LANGUAGE MyLanguageOption #-}
module Bar where

$ ghc-6.4.1 -E -cpp -optP-P Bar.hs
$ cat Bar.hspp

{-# OPTIONS_GHC -X MyLanguageOption #-}
module Bar where





___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Quasi quoting

2010-02-01 Thread Malcolm Wallace
 (ii) If [pads| is a lexeme, then some list comprehensions become  
illegal,


I am not myself a TH or QQ user, but it has always bothered me  
slightly that the syntax for them steals some valid list comprehensions.


Of the alternative syntaxes you suggest...


My gut feel is to go with [|pads| ... |].


... this one feels the nicest, because [|  |] is an ascii  
approximation of the common syntactic brackets used in semantic  
specifications.  In some ways, to make the correspondence even closer,


pads [| ... |]

might be even better, although I realise that this might present new  
problems.


Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GHC ParseTree Module

2011-01-03 Thread Malcolm Wallace
You will be more likely to get an answer on the ghc-users mailing list  
(cc'ed).  The ghc developers rarely follow -cafe.


On 1 Jan 2011, at 20:36, Jane Ren wrote:


Hi,

Does anyone know what GHC module gets the AST and type info of some  
source code?  This is the GHC module that converts all of Haskell  
into an AST with a small number of pattern cases, where each AST  
node is annotated with the Haskell type.


Thanks
___
Haskell-Cafe mailing list
haskell-c...@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe



___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: RFC: migrating to git

2011-01-10 Thread Malcolm Wallace

On 10 Jan 2011, at 14:02, Gregory Collins wrote:

+1. I don't have a lot of skin in this particular game (I'm not
currently a GHC contributor and am unlikely to become one in the near
future), but I can offer some anecdotal evidence:


As another non-GHC contributor, my opinion should probably also count  
for little, but my experience with git has been poor.


I have used git daily in my job for the last year.  Like Simon PJ, I  
struggle to understand the underlying model of git, despite reading  
quite a few tutorials.  I have a high failure rate with attempting  
anything beyond the equivalents of darcs record, push, and pull.


When I use darcs, my local workflow typically involves lots of amend- 
record, cherry-picking, and multiple repos/branches.  I have tried to  
do these things in git a few times and failed miserably.  I am an old- 
fashioned unix command-line lover, but I find using the git command- 
line is next to impossible, and as a consequence do almost everything  
in git gui.  If the gui interface does not let me do an action, then I  
often can't work out how to do it at all, even after googling.


Mind you, some other people at work somehow manage to use git's  
support for branching reasonably successfully.  But we have occasional  
mishaps where a repo is made totally unusable by somebody making a  
tiny mistake with their branching commands.  Our standard advice at  
work for people who get their repo muddled is to throw it away, re- 
clone the master, and manually re-code their local changes from  
scratch (with the help of diff).


If I were considering contributing minor patches to a project, the use  
of git would probably not deter me too much - I can cope with the  
simple stuff.  But if I wanted more major involvement, git would  
definitely cause me to think twice about whether to bother.


Regards,
Malcolm


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: RFC: migrating to git

2011-01-11 Thread Malcolm Wallace


On 10 Jan 2011, at 22:37, Daniel Peebles wrote:

So the basic point seems to be: if you know how to use a tool, you  
don't usually curse and swear when you use it. If you don't, you  
tend to swear a lot!


There is a meta-point though - how easy is it to learn the tool?

Regards,
Malcolm

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: hoogling GHC

2011-03-05 Thread Malcolm Wallace

Ranjit,


I'd like to build a hoogle database that indexes the GHC source.
Can anyone point me to how I might do that? (Or better, to a  
preexisting database?)



The author of Hoogle, Neil Mitchell, is currently on holiday, but I'm  
sure he will have some good advice for you when he returns.


In the meantime, the relevant portion of the Hoogle manual is here:
http://www.haskell.org/haskellwiki/Hoogle#Database_Creation

and a blog post with instructions is here:
http://neilmitchell.blogspot.com/2008/08/hoogle-database-generation.html

 (I've noticed that make haddock generates a bunch of .txt files.
 Is there some easy way to scour the directories and build a single
 Hoogle database from them?)

I imagine some simple shell scripting would achieve that, starting with
find haddockBaseDir -name *.txt -print | ...

Regards,
Malcolm

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: hoogling GHC

2011-03-05 Thread Malcolm Wallace
The final stumbling block is getting the local webserver (hoogle  
server)
to also search the above database. I'm sure there must be some  
simple way I
can pass the name of the database as an argument when I boot up the  
server,

but I can't seem to find it...


Have you found the various versions of the web deployment procedure yet?

deploy.txt:  instructions to follow manually (seems to be up-to-date)
deploy.sh:   a shell script version to run locally (may be old)
Deploy.hs:   a haskell version to run remotely (may also be old)

Obviously those scripts are tailored to the official installation, but  
there are some clues in there, for instance the steps


cabal configure --datadir=/srv/web/haskell.org/hoogle/ -- 
datasubdir=datadir -O2


and

Upload datadir/resources to /srv/web/haskell.org/hoogle/datadir/ 
resources
Upload datadir/databases/* to /srv/web/haskell.org/hoogle/datadir/ 
databases


Regards,
Malcolm

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: hsc2hs on Mac

2011-05-13 Thread Malcolm Wallace
 hsc2hs converts
  (#const sizeof(struct stat))
  (#peek struct stat, st_mtimespec)
 to 
  108
  36
 but the correct values are
  144
  32.
 
 Is this a bug of hsc2hs?

Not directly.  hsc2hs calls the C compiler to determine these numbers.  It 
seems it is calling gcc-4.0 rather than gcc-4.2.  It might be a bug that it is 
calling the wrong compiler, but that might just be misconfiguration in your 
environment, or in the Haskell Platform.

 gcc-4.0 says sizeof (struct stat) is 108 while gcc-4.2 (default) says
 that is 144.



___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: How to install GhC on a Mac without registering?

2011-06-06 Thread Malcolm Wallace

On 6 Jun 2011, at 13:49, Lyndon Maydwell wrote:

 I would be fantastic if XCode wasn't a dependency.  ...
 
 Not to detract at all from the work of the wonderful GHC and Haskell
 Platform contributors in any way. For me it would just make it that
 much easier to convince mac-using friends to give Haskell a try.

The ghc team already bundle a copy of gcc in their Windows distribution, 
precisely because it can be fiddly to get a working copy of gcc for that 
platform otherwise.  I wonder if they would consider the possibility of 
shipping gcc on Mac too?  (There may be good reasons not to do that, but let's 
have the discussion.)

Regards,
Malcolm

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: How to install GhC on a Mac without registering?

2011-06-12 Thread Malcolm Wallace

On 10 Jun 2011, at 02:15, Manuel M T Chakravarty wrote:

 Anybody who is halfway serious about developing software on a Mac will have 
 Xcode installed anyway.

As the original poster clarified, the motivating use-case is education 
(specifically a class of 12-13 year olds.)  These are not serious developers, 
but they have the potential to become serious.  Placing unnecessary hurdles in 
their way will diminish the chances of their discovering Haskell to be a 
beautiful language.

Having said that, I do think that Hugs (or maybe Helium) would be a more 
appropriate environment for teaching the basics to young students.

Regards,
Malcolm


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GHC and Haskell 98

2011-06-18 Thread Malcolm Wallace
As one of the few people who has habitually used Haskell'98 wherever possible, 
I favour plan A.  As I recently discovered, in ghc 7 it is already very fragile 
to attempt to depend on both the base and haskell98 packages simultaneously.  
In most cases it simply doesn't work.  Removing those few remaining cases where 
it happens to work by accident would be a good move.

Regards,
Malcolm

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: integer-simple

2011-07-31 Thread Malcolm Wallace
I notice that ghci is loading integer-simple before loading base.  This at 
least explains why it cannot find a symbol from the base package - it hasn't 
been loaded yet.  So the question is why does integer-simple use any function 
from the base package at all? I'm fairly sure that the dependency graph is such 
that it should not.



On 30/07/2011, at 22:37, Chris Dornan ch...@chrisdornan.com wrote:

 Hi All,
 
  
 
 I thought I may as well try the same experiment 7.2.1-RC1 on completely 
 different hardware (a network v-server running CentOS 5 with ghc-6.12.3 
 installed) and indeed:
 
  
 
 ghci
 
 GHCi, version 7.2.0.20110728: http://www.haskell.org/ghc/  :? for help
 
 Loading package ghc-prim ... linking ... done.
 
 Loading package integer-simple ... linking ... ghc: 
 /usr/local/ghc/7.2.0.20110728/lib/ghc-7.2.0.20110728/integer-simple-0.1.0.0/HSinteger-simple-0.1.0.0.o:
  unknown symbol `base_ControlziExceptionziBase_patError_info'
 
 ghc: unable to load package `integer-simple'
 
  
 
 This has to be the way I am configuring the build – as y’all can see I am 
 configuring with a non-standard prefix, but otherwise it is a case of a clean 
 build from virginal sources with the appended build.mk.
 
  
 
 I think I am going to have to start looking at the failure mechanism…
 
  
 
 Chris
 
  
 
 snipety-snip
 
  
 
 # 
 -
 
 # A Sample build.mk
 
 #
 
 # Uncomment one of the following BuildFlavour settings to get the desired
 
 # overall build type, and then tweak the options in the relevant section
 
 # below.
 
  
 
 # Uncomment one of these to select a build profile below:
 
  
 
 # Full build with max optimisation (slow build)
 
 #BuildFlavour = perf
 
  
 
 # Fastest build (libs unoptimised):
 
 BuildFlavour = quickest
 
  
 
 # Fast build with optimised libraries:
 
 #BuildFlavour = quick
 
  
 
 # Profile the stage2 compiler:
 
 #BuildFlavour = prof
 
  
 
 # A development build, working on the stage 1 compiler:
 
 #BuildFlavour = devel1
 
  
 
 # A development build, working on the stage 2 compiler:
 
 #BuildFlavour = devel2
 
  
 
 GhcLibWays = v
 
  
 
 #  1. A Performance/Distribution build
 
  
 
 ifeq $(BuildFlavour) perf
 
  
 
 # perf matches the default settings, repeated here for comparison:
 
  
 
 SRC_HC_OPTS = -O -H64m
 
 GhcStage1HcOpts = -O -fasm
 
 GhcStage2HcOpts = -O2 -fasm
 
 GhcHcOpts   = -Rghc-timing
 
 GhcLibHcOpts= -O2 -XGenerics
 
 GhcLibWays += p
 
  
 
 ifeq $(PlatformSupportsSharedLibs) YES
 
 GhcLibWays += dyn
 
 endif
 
  
 
 endif
 
  
 
 #  A Fast build --
 
  
 
 ifeq $(BuildFlavour) quickest
 
  
 
 SRC_HC_OPTS= -H64m -O0 -fasm
 
 GhcStage1HcOpts= -O -fasm
 
 GhcStage2HcOpts= -O0 -fasm
 
 GhcLibHcOpts   = -O0 -fasm
 
 SplitObjs  = NO
 
 HADDOCK_DOCS   = NO
 
 BUILD_DOCBOOK_HTML = NO
 
 BUILD_DOCBOOK_PS   = NO
 
 BUILD_DOCBOOK_PDF  = NO
 
  
 
 endif
 
  
 
 #  A Fast build with optimised libs --
 
  
 
 ifeq $(BuildFlavour) quick
 
  
 
 SRC_HC_OPTS= -H64m -O0 -fasm
 
 GhcStage1HcOpts= -O -fasm
 
 GhcStage2HcOpts= -O0 -fasm
 
 GhcLibHcOpts   = -O -fasm
 
 SplitObjs  = NO
 
 HADDOCK_DOCS   = NO
 
 BUILD_DOCBOOK_HTML = NO
 
 BUILD_DOCBOOK_PS   = NO
 
 BUILD_DOCBOOK_PDF  = NO
 
  
 
 endif
 
  
 
 #  Profile the stage2 compiler ---
 
  
 
 ifeq $(BuildFlavour) prof
 
  
 
 SRC_HC_OPTS= -H64m -O0 -fasm
 
 GhcStage1HcOpts= -O -fasm
 
 GhcStage2HcOpts= -O -fasm
 
 GhcLibHcOpts   = -O -fasm
 
  
 
 GhcLibWays += p
 
 GhcProfiled= YES
 
  
 
 SplitObjs  = NO
 
 HADDOCK_DOCS   = NO
 
 BUILD_DOCBOOK_HTML = NO
 
 BUILD_DOCBOOK_PS   = NO
 
 BUILD_DOCBOOK_PDF  = NO
 
  
 
 endif
 
  
 
  
 
 #  A Development build (stage 1) -
 
  
 
 ifeq $(BuildFlavour) devel1
 
  
 
 SRC_HC_OPTS= -H64m -O -fasm
 
 GhcLibHcOpts   = -O -dcore-lint
 
 GhcStage1HcOpts= -Rghc-timing -O0 -DDEBUG
 
 GhcStage2HcOpts= -Rghc-timing -O -fasm
 
 SplitObjs  = NO
 
 HADDOCK_DOCS   = NO
 
 BUILD_DOCBOOK_HTML = NO
 
 BUILD_DOCBOOK_PS   = NO
 
 BUILD_DOCBOOK_PDF  = NO
 
  
 
 endif
 
  
 
 #  A Development build (stage 2) -
 
  
 
 ifeq $(BuildFlavour) devel2
 
  
 
 SRC_HC_OPTS= -H64m -O -fasm
 
 GhcLibHcOpts   = -O -dcore-lint
 
 GhcStage1HcOpts= -Rghc-timing -O -fasm
 
 GhcStage2HcOpts= -Rghc-timing -O0 -DDEBUG
 
 SplitObjs  = NO
 
 HADDOCK_DOCS   = NO
 
 BUILD_DOCBOOK_HTML = NO
 
 BUILD_DOCBOOK_PS   = NO
 
 BUILD_DOCBOOK_PDF  = NO
 
  
 
 endif
 
  
 
 # 
 

Re: Terminal does not reset correctly with System.Console.SimpleLineEditor

2004-11-07 Thread Malcolm Wallace
Einar Karttunen [EMAIL PROTECTED] writes:

 It appears that the console is not reset correctly with
 System.Console.SimpleLineEditor. The terminal does not 
 echo characters until it is reset. 

The issue here is the order in which the library makes calls to
hSetBuffering and system(stty icanon echo) to reset the terminal.
For ghc-6, they are in the wrong order, although for nhc98 and ghc-5,
the order doesn't matter.  Hence, a simple fix is to swap these calls
over, as I have just done in CVS.

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


Re: Looing for advice on profiling

2004-11-09 Thread Malcolm Wallace
Duncan Coutts [EMAIL PROTECTED] writes:

 I'm looking for some advice on profiling and any suggestion on what
 might be going on with this program.

One suggestion might be to serialise (key,value) pairs to file as
they are first encountered, rather than waiting until they are all
inside FiniteMaps.  That would eliminate the time you are currently
spending on lookups.  (A subsequent run would then need to do the
insertion of binary (key,value)s, rather than having them already
ordered, but at least you save the textual parsing cost there.)

 A major problem no doubt is space use. For the large gtk/gtk.h, when I
 run with +RTS -B to get a beep every major garbage collection, the
 serialisation phase beeps continuously while the file grows.
 Occasionally it seems to freeze for 10s of seconds, not dong any garbage
 collection and not doing any file output but using 100% CPU, then it
 carries on outputting and garbage collecting furiously. I don't know how
 to work out what's going on when it does that.

One guess might be generational collection: fast beeps are for the
current generation, pauses are older generations?

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


Re: GHC 6.4 release candidates available

2005-02-10 Thread Malcolm Wallace
Simon Marlow [EMAIL PROTECTED] writes:

 We are finally at the release candidate stage for GHC 6.4.  Snapshots
 with versions 6.4.20050209 and later should be considered release
 candidates for 6.4.

Using: ghc-6.4.20050209-i386-unknown-linux.tar.bz2

$ cat hello.hs
main = putStrLn hello world
$ ghc--6.4.20050209 -o hello hello.hs
ld: cannot find -lHSbase_cbits
collect2: ld returned 1 exit status
$

Pretty much a show-stopper.
Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GHC 6.4 release candidates available

2005-02-10 Thread Malcolm Wallace
Simon Marlow [EMAIL PROTECTED] writes:

 We are finally at the release candidate stage for GHC 6.4.
 Please test if you're able to, and give us feedback.

In versions 5.00 = ghc = 6.2.2, the result of

ghc -v 21 | head -2

was something like

Glasgow Haskell Compiler, Version 6.2.2, 
Using package config file: /grp/haskell/lib/ghc-6.2.2/package.conf

whereas with 6.4, these two lines have been swapped:

Reading package config file: 
/usr/malcolm/local/lib/ghc-6.4.20050209/package.conf
Glasgow Haskell Compiler, Version 6.4.20050209, 

and the Using package config message has become Reading package
config.  These changes are minor and unnecessary: in particular they
make the detection of configuration information (by hmake) rather
more complicated than it ought to be.  I know this is a pretty trivial
complaint, but the -v behaviour has been stable for a few years now,
so why change it arbitrarily?

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GHC 6.4 release candidates available

2005-02-10 Thread Malcolm Wallace
Simon Marlow [EMAIL PROTECTED] writes:

  and how do you find out what $libdir refers to...?
 
 ghc --print-libdir

Cool.  Will fix hmake to use it.
Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GHC 6.4 release candidates available

2005-02-10 Thread Malcolm Wallace

$ ghc-pkg-6.4.20050209 --show-package=base --field=import_dirs
[/usr/malcolm/local/lib/ghc-6.4.20050209/imports]

yet

$ ghc-pkg-6.4.20050209 --show-package=base-1.0 --field=import_dirs
ghc-pkg: cannot find package base-1.0

$ ghc-pkg-6.4.20050209 --list-packages
/usr/malcolm/local/lib/ghc-6.4.20050209/package.conf:
rts-1.0, base-1.0, haskell98-1.0, template-haskell-1.0, ...

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GHC 6.4 release candidates available

2005-02-11 Thread Malcolm Wallace
Simon Marlow [EMAIL PROTECTED] writes:

  $ ghc-pkg-6.4.20050209 --show-package=base-1.0 --field=import_dirs
  ghc-pkg: cannot find package base-1.0
 
 BTW, we recommend you migrate to using the new command-line syntax for
 ghc-pkg at some point.

Documented where?  The GHC user guide doesn't seem to be included in
the download bundle.

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GHC 6.4 release candidates available

2005-02-11 Thread Malcolm Wallace
Simon Marlow [EMAIL PROTECTED] writes:

 I'm having some trouble with the XML docbook formatting tools right now.
 If you have a source tree, 'make html' should work in
 ghc/docs/users_guide.

Sadly, not.

$ cvs checkout ... 
$ cd fptools
$ autoreconf
$ ./configure
[]
checking for xmllint... /usr/bin/xmllint
checking for DocBook DTD... ok
checking for xsltproc... /usr/bin/xsltproc
checking for DocBook XSL stylesheet directory... ./configure: line 4517:  
1746 Segmentation fault  $XsltprocCmd ${fp_var}/html/docbook.xsl 
conftest.xml /dev/null 21
./configure: line 4517:  1799 Segmentation fault  $XsltprocCmd 
${fp_var}/html/docbook.xsl conftest.xml /dev/null 21
no
[]

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GHC 6.4 release candidates available

2005-02-11 Thread Malcolm Wallace
 Please test if you're able to, and give us feedback.

It looks like GADTs (or something else new) conflict with normal
Haskell'98 type inference.  The following example used to compile
just fine with all previous versions of ghc and nhc98.

  $ ghc-6.4.20050210   -package lang-c  -o Parse.o Parse.hs

  Parse.hs:209:4:
Couldn't match the rigid variable `a' against the rigid variable `a1'
  `a' is bound by the type signature for `parseValdef'
  `a1' is bound by the type signature for `parseWhere'
  Expected type: Parser (Decls TokenId) [PosToken] a1
  Inferred type: Parser (Decls TokenId)
[(Pos, Lex, Lexical.LexState, 
[LexPre.PosTokenPre])]a
In the expression:
lit L_where) `revChk` lcurl) `revChk` parseDecls) `chk` rcurl)
`orelse` (parse (DeclsParse []))
In the definition of `parseWhere':
parseWhere = lit L_where) `revChk` lcurl) `revChk` parseDecls) 
`chk` rcurl)
 `orelse` (parse (DeclsParse []))

The quoted expressions look a little bit hairy, but if you examine
the explicit type signatures in question, it is very clear that there
should be no error here.  To reproduce the bug, just build the nhc98
compiler proper.

$ wget ftp://ftp.cs.york.ac.uk/pub/haskell/nhc98/nhc98src-1.17.tar.gz
$ tar zxf nhc98src-1.17.tar.gz
$ ./configure --buildwith=ghc-6.4.20050210
$ make basic

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: compiling GHC with a custom path to GCC

2005-02-17 Thread Malcolm Wallace
Seth Kurtzberg [EMAIL PROTECTED] writes:

 There has to be one, because the problem occurs when you compile gcc 
 with gcc.  I'll look for a specific bug report.  It happens much more 
 frequently with 3.x than with 2.95, in my testing, but that was not a 
 test of compiling Haskell, so I have no frequency information, specifically.

Sounds like a CPU-overheating problem to me.  It is well known that
running an inadequately cooled processor at 100% for an extended
period will cause random crashes.  There are third-party reports
that it happens with Linux kernel builds, and I have personally seen
it with builds of nhc98 and Hat.  When I replaced the CPU fan, the
problems disappeared.

 The other problem for the gcc people is the fact that it occurs 
 randomly.  The behavior has changed; 3.4 will crash in a different place 
 than 3.3.  If the program is large enough, it will happen.

Non-repeatable crashes certainly point the finger first at hardware
rather than software.  Could also be deteriorating memory chips -
but that is likely to bring the whole machine down eventually.

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: compiling GHC with a custom path to GCC

2005-02-18 Thread Malcolm Wallace
Seth Kurtzberg [EMAIL PROTECTED] writes:

 Simon, you'll never give up.  The crashes are absolutely repeatable.  
 The fact that I haven't identified a deterministic way to reproduce them 
 does not in any way imply that a deterministic way to reproduce them 
 does not exist.  And, as I've said, you are essentially claiming that a 
 total of over 100 machines all have the same hardware problem, that 
 never ever occurs unless gcc is running.  You know that isn't true.  You 
 can, on the same machines, compile the same code with a different 
 compiler hundreds of times (which I did; I left it running on two 
 machines for a month) without a single problem.  That is a software problem.

OK, calm down.  I, for one, suggested the possibility of a hardware
fault because your original message on the subject of gcc crashes did
not mention the possibility at all, and I thought perhaps it was a
factor you had not considered.  Obviously you have indeed considered it
in quite some detail, and concluded that hardware is not a factor here.
But because we didn't know that, the suggestion was intended to help you
explore new avenues to tracking down the fault, not to annoy you.

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Configuring in directories with spaces fails in ghc6.4

2005-02-22 Thread Malcolm Wallace
Simon Marlow [EMAIL PROTECTED] writes:

  It seems the ghc 6.4 release candidates' configure scripts fail if you
  run them in a directory structure containing a space.
 
 Quite possibly.  No doubt we'd have to add a million quotes to the build
 system to fix this; it's not going to happen any time soon.  

Yes.  Someone recently reported the same problem with nhc98's configure
script, and I actually tried adding the quotes.  It is nightmarish -
you'll quickly discover a need for quotes inside quotes and worse,
depending on how many levels of shells/tools/Makefiles a variable gets
passed through.  In the end, it was far simpler to abandon the idea.

However, it could be worthwhile halting with an error message.

case `pwd` in
  *' '*)
echo Error: nhc98 will not build in a directory with spaces anywhere
echoin the full pathname.
echo Suggestion: move the build tree somewhere else.
exit 1 ;;
esac

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GHC 6.4 release candidates available (breakage on suse 9.2 x86 or x86-64)

2005-02-24 Thread Malcolm Wallace
Just a quick comment on a couple of things Brian Strand writes:

 Or is ghc/Haskell established enough that
 the existence of some Haskell compiler is taken for granted nowadays?

Ghc is not written in pure Haskell - it is written in Ghc Haskell,
i.e. it uses many extensions and internal libraries not available
in all other Haskell implementations.  Thus, you really need ghc to
bootstrap ghc.

 Would it be unreasonable to include the unregisterised .hc files with
 a source distribution (or .hc files for popular platforms), so that
 a Haskell novice such as myself could do a ./configure  make 
 make install?  If configure detected no ghc, perhaps it could do the
 bootstrap automagically.

This is what nhc98 does - supplies platform independent .hc files for
bootstrapping via gcc if no existing Haskell compiler is installed.
However, nhc98 uses a bytecode VM, so it produces code that is 3x
- 15x slower than ghc, (currently) lacks many of the lower-level
libraries, and implements very few language extensions.  Thus it has
a smaller user base, and smaller maintainer base too (therefore not
much ongoing development).

Ideally, if ghc were implemented in something closer to Haskell'98,
it would be possible to double-bootstrap up from gcc - nhc98 -
ghc unregisterised - ghc registerised, on almost any new platform.
But the amount of work required to 98-ify ghc is considerable (there
are 148 kLoC to check), and it is hard to say whether it would
be worthwhile.  Maybe someone fancies tackling it as a medium-size
project?

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GHC 6.4 release candidates available

2005-02-28 Thread Malcolm Wallace
Simon Peyton-Jones [EMAIL PROTECTED] writes:

 I think I've fixed this (on the head anyway; simon will merge to branch
 shortly).  Care to try again?

Yup, the toplevel rigid type-variable problem seems to have been fixed,
thanks.  nhc98 now builds as expected with ghc-6.4.

BTW, there seems to be a small documentation-packaging fault in the
linux binary distribution.  You may be aware of it already.

$ make install
...
if test -d share/html; \
then cp -r share/html/* /usr/malcolm/local/share/ghc-6.4.20050227/html; \
fi
for i in share/*.ps; do \
cp $i /usr/malcolm/local/share/ghc-6.4.20050227 ; \
done
cp: cannot stat `share/*.ps': No such file or directory
$

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GHC 6.4 release candidates available

2005-03-02 Thread Malcolm Wallace
Ian Lynagh [EMAIL PROTECTED] writes:

 ghc-6.4.20050228-src.tar.bz2
 
 I think you have unswapped the first two lines of
 ghc -v 21 | head -2 but not changed Reading back to Using, so
 old hmakes are still broken (old includes the latest release, I
 believe).

There are a couple of other configuration changes needed in hmake to
support ghc-6.4 as well, so there will be a new release shortly.

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GHC 6.4 Release Candidate Binary for Mac OS X

2005-03-04 Thread Malcolm Wallace
Wolfgang Thaller [EMAIL PROTECTED] wrote:

 I've uploaded a Mac OS X installer based on the stable tree from March 
 2nd + the patches I committed yesterday at:
 
 http://opeongo.cas.mcmaster.ca/~wolfgang/GHC-6.4.20050302.pkg.zip

$ ghc --version
dyld: /usr/local/lib/ghc-6.4/ghc-6.4 can't open library: 
/Users/wolfgang/GHC/stable-build/libraries/readline/libHSreadline_dyn.dylib  
(No such file or directory, errno = 2)
Trace/BPT trap

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Another GHC 6.4 Release Candidate Binary for Mac OS X

2005-03-10 Thread Malcolm Wallace
  Another Mac OS X installer:
  http://opeongo.cas.mcmaster.ca/~wolfgang/GHC-6.4.20050308.pkg.zip

Works fine for me too.

 The double-clickable icons for GHCi are great,

When I double-click the icon, I get *two* Terminal windows started, one
running ghci, the other just an ordinary shell.  Is this intended?

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


cpphs (was Re: Haskell on Red Hat Enterprise...)

2005-03-17 Thread Malcolm Wallace
Andy Moran [EMAIL PROTECTED] writes:

  With 3.4, changes were made to the 
 -traditional version of the C preprocessor that make it incompatible 
 with the way in which many of the Haskell modules in the GHC source tree 
 reify make/build variables as Haskell strings.
 
 Have we converged on a long-term solution for this problem? Is hscpp 
 ready for the job?

I believe cpphs is in good shape.  There has been one bug report, and
no new feature requests, in the last 4 months since 0.8 was released,
with 235 downloads of that version.  Over a slightly longer period,
it has been used internally by hmake and nhc98 in preference to cpp,
with no visible problems.

With the attached compatibility script, it is largely possible to use
cpphs as a drop-in replacement for cpp.  (The script just translates
the command-line argument format.)  e.g.
ghc -cpp -pgmP cpphs.compat 
works as expected.

The only real issue currently preventing ghc from adopting cpphs is
ideological (GPL licensing).

http://haskell.org/cpphs/

Regards,
Malcolm

file cpphs.compat

#!/bin/sh
#   A minimal compatibility script to make cpphs accept the same
#   arguments as real cpp, wherever possible.

# Set this variable as the path to your installed version of cpphs:
CPPHS=/usr/local/bin/cpphs

processArgs () {
  TRADITIONAL=no
  STRIP=yes
  INFILE=-
  OUTFILE=-
  while test $1 != 
  do
case $1 in
  -D)shift; echo -D$1 ;;
  -D*)   echo $1 ;;
  -U)shift; echo -U$1 ;;
  -U*)   echo $1 ;;
  -I)shift; echo -I$1 ;;
  -I*)   echo $1 ;;
  -o)shift; echo -O$1 ;;
  -o*)   echo -O`echo $1 | cut -c3-` ;;
  -std*) ;; # ignore language spec
  -x)shift ;;   # ignore language spec
  -ansi*)TRADITIONAL=no ;;
  -traditional*) TRADITIONAL=yes ;;
  -include)  shift; echo $1 ;;
  -P)echo --noline ;;
  -C)STRIP=no ;;
  -CC)   STRIP=no ;;
  -A)shift ;;   # strip assertions
  --help)echo $1 ;;
  -version)  echo -$1 ;;
  --version) echo $1 ;;
  -*);; # strip all other flags
  *) if [ $INFILE = - ]
 then INFILE=$1
 else OUTFILE=$1
 fi ;;
esac
if test $1 != ; then shift; fi
  done
  if [ $TRADITIONAL = no ]; then echo --hashes;   fi
  if [ $STRIP = yes ];  then echo --strip;fi
  echo $INFILE
  if [ $OUTFILE != - ]; then echo -O$OUTFILE; fi
}

exec $CPPHS `processArgs $@`
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: cpphs (was Re: Haskell on Red Hat Enterprise...)

2005-03-17 Thread Malcolm Wallace
Andy Moran [EMAIL PROTECTED] writes:

 I notice that cpphs understands CPP stringification (if invoked with 
 --hashes). Most of the gcc 3.4 failures (in fact, all of that I've seen) 
 have to do with fooling -traditional into turning macro constants into 
 Haskell strings, which can more readily be done with the #-operator. So, 
 would using cpphs mean we could do away with the string gap hack?

Without seeing the examples in question, I can't say for definite, but
cpphs /does/ preserve string gaps in source code in all cases.  In
addition, you can paste symbol values into strings using either the
ANSI stringification operator (#) or the traditional behaviour of
expansion within quotes (SYMBOL).

 What implications does the LGPL have for a GHC binary that was built 
 using  cpphs, if the GHC binary were used solely within an organization 
 (i.e. not distributed)?

Both the GPL and LGPL lay obligations on the user of the code only if
they re-distribute it - it has no impact on internal use if there is no
re-distribution.

 What if cpphs were distributed with such a GHC 
 binary as an executable?

If cpphs is distributed as a stand-alone binary, then you must respect
the conditions of the GPL with regard to that program (only), i.e.
permit re-distribution, publish modified source code etc.  This by itself
does not place any further restrictions on any of your own software you
distribute with it.  In GPL terms, this is mere aggregation, which is
non-infective.  Your own GHC-produced binary can have any licence you like.

It is only if you were to re-use the code from cpphs as a library linked
into your own software, that restrictions would apply to your software.
In the case of the LGPL, the end user must be given the right to remove
cpphs and replace it with a newer version, which tends to imply that you
need to link it dynamically rather than statically.  However, I expect very
few people would need to incorporate cpphs as a library - the stand-alone
executable situation is far more likely.

Regards,
Malcolm

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: cpphs (was Re: Haskell on Red Hat Enterprise...)

2005-03-18 Thread Malcolm Wallace
Andy Moran [EMAIL PROTECTED] writes:

 -- hackery to convice cpp to splice GHC_PKG_VERSION into a string
 version :: String
 version = tail \
 \ GHC_PKG_VERSION

OK, it turns out that this is pretty tricky to do in cpp, even with
full scope of -ansi or -traditional behaviour.  In fact, the hack
shown is the only way to achieve it (demonstrated below), and the
hack fails with cpphs /because/ of the string gap!  By contrast,
cpphs --text makes the original task very straightforward.
(The option turns off source-code lexing of the file as Haskell,
so that macros can be expanded within quotes.)

Here are a variety of ways you might attempt stringification:

#define GHC_PKG_VERSION 6.2.2
-- hackery to convice cpp to splice GHC_PKG_VERSION into a string
version :: String
version = tail \ 
\ GHC_PKG_VERSION

version2 = GHC_PKG_VERSION

#define v3 GHC_PKG_VERSION
version3 = v3

#define stringify(s) #s
version4 = stringify(GHC_PKG_VERSION)

#define stringify2(s) s
version5 = stringify2(GHC_PKG_VERSION)

And here are the results:

cpp -ansi
version = tail \ GHC_PKG_VERSION
version2 = GHC_PKG_VERSION
version3 = GHC_PKG_VERSION
version4 = GHC_PKG_VERSION
version5 = s

cpp -traditional
version = tail \
\ 6.2.2
version2 = GHC_PKG_VERSION
version3 = GHC_PKG_VERSION
version4 = #6.2.2
version5 = GHC_PKG_VERSION

cpphs
version = tail \
\ GHC_PKG_VERSION
version2 = GHC_PKG_VERSION
version3 = GHC_PKG_VERSION
version4 = #6.2.2
version5 = GHC_PKG_VERSION

cpphs --hashes
version = tail \
\ GHC_PKG_VERSION
version2 = GHC_PKG_VERSION
version3 = GHC_PKG_VERSION
version4 = GHC_PKG_VERSION
version5 = GHC_PKG_VERSION

cpphs --text
version = tail \
\ 6.2.2
version2 = 6.2.2
version3 = 6.2.2
version4 = #6.2.2
version5 = 6.2.2

cpphs --text --hashes
version = tail \
\ 6.2.2
version2 = 6.2.2
version3 = 6.2.2
version4 = 6.2.2
version5 = 6.2.2


 HEAD uses a Makefile-generated Version.hs instead. Simon M.: are all 
 instances of the above trick replaced by analogues of this much neater 
 mechanism?

I agree that, ultimately, generating the source code directly is
better than using cpp-ish stuff.

 So, cpphs' version of traditional is truer to tradition than gcc's, it 
 seems.

Well, no not really: cpphs is pretty close to cpp -traditional, and cpphs
--hashes is pretty close to cpp -ansi, with the treatment of string gaps
causing the only slight differences.

 gcc -E -traditional -x c doesn't expand within quotes, which is 
 why hacks like the above were introduced.

Whilst there /is/ a visible difference between cpp and cpphs for
expansion within quotes, where the quotes are located within the
definition of the macro (see version5), it isn't relevant here.

Your highlighted problem was to do with expansion of macros inside
quotes within the main body of the file.  Ordinary cpp has no ability
to do this whatsoever - the file is always lexed for strings and
comments - whilst cpphs is more flexible.

Regards,
Malcolm

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: HOME: getEnv: does not exist

2005-04-18 Thread Malcolm Wallace
Niklas Broberg [EMAIL PROTECTED] writes:

 when I try to use runghc to execute cgi scripts in apache (on redhat
 linux), they all fail with with the message HOME: getEnv: does not
 exist. I assume this means that GHC is trying to find the HOME dir of
 the user for some reason, and fails since apache runs as nobody. Could
 someone shed some light on this matter for me?

I think runghc is acting like GHCi, and trying to read the file
$HOME/.ghci on startup.

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


multiple versions of ghc

2005-05-05 Thread Malcolm Wallace
Is it true that on unix, tools like ghc-pkg-6.2.2 and ghc-pkg-6.4
may co-exist, but on Windows the version number is not present,
so a single executable is simply called ghc-pkg.exe?

If so, how do Windows users deal with having more than one version
of ghc installed simultaneously?  Is this just a bug/oversight that
can be fixed?

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: hat, ghc

2005-09-02 Thread Malcolm Wallace
Frederik Eaton [EMAIL PROTECTED] writes:

 By the way, can I make a request to have the hmake default be to use
 the environment?

Ian Lynagh recently added this capability to hmake, but it wasn't
documented (until yesterday).  The relevant option is
hmake-config add-dyn ghc
which causes the version of ghc to be probed every time hmake is run,
rather than only once at configure-time.  Thus, it should pick up
the current environment settings as needed.

 Now, it appears to be looking for 'ghc-pkg' in the library directory
 of 'ghc' (rather, again, than in $PATH)

Well, hmake absolutely needs to use the ghc-pkg that belongs to the
particular version of ghc.  The heuristic used to find it might be
slightly fragile, but it is the best available, and indeed it is
based on the information given by ghc itself.  If the executable
has been moved such that querying ghc for its location is no longer
reliable, that's tough to fix.

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: profile not showing it all?

2005-09-08 Thread Malcolm Wallace
Niels [EMAIL PROTECTED] writes:

 since my application takes up way to much memory, i decided to profile it
 (compile d it with -prof and -auto-all). After running it with +RTS -hc, it
 shows a graph that reaches a peak at around 85mb.
 However, when i check the memory usage with 'top' i see the application reach
 over 300mb.

Are you checking 'top' on the profiled version?  It will show more heap
usage than the profile itself, because some heap space is taken up by
the profiling data itself.  But of course the profile is only supposed
to report the heap space that is used in normal usage, excluding the
overhead used to build the report.  The profiling overhead can certainly
double space usage, and with cost-centre stacks, it could be even
higher.  Don't forget to subtract the static size of the executable too.

If, however, you are comparing /unprofiled/ 'top' with the profile, it
suggests a fault in ghc's profiling code.

Regards,
Malcolm

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GADT question

2005-10-10 Thread Malcolm Wallace
Henrik Nilsson [EMAIL PROTECTED] writes:

   I get an error No instance for (Fractional a) arising from the use of
   '/'  This seems odd to me, since Div is constrained to have
   fractional arguments.  Is there something obvious I'm missing?
 
 Unless GADTs are handled specially, and I don't think they are in this 
 case, this problem is not specific to GADTs but related to how
 type constraints on constructors are handled in general. Basically, a
 constraint on a constructor has no effect beyond beyond constraining 
 what the  constructor can be applied to (see the Haskell 98 report 
 4.2.1). In particular, when you take a constructed value apart through
 pattern matching, the constraints do not come into play: hence the no
 instance message.

And in case anyone is wondering, you could fix the original program by
adding the constraint to the function signature:

eval :: Fractional a = Term a - a

although this is likely more constrained than the OP wanted.

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [Haskell] Re: lambda calculus theory

2005-11-07 Thread Malcolm Wallace
Marc A. Ziegert [EMAIL PROTECTED] writes:

  I'm searching for a good mathematical oriented introduction to the  
  theory of lambda calculus or other theoretical foundations of Lisp/ 
  Haskell, i.e. monads or such (of course in the web there are much  
  hints, but what is the best for mathematicans foreign to this field)
 
 i'm searching for such lectures/papers/scripts, too.

The classic textbook on lambda calculus is 

The Lambda Calculus: Its Syntax and Semantics.
Henk Barendregt.
(Hardback, Elsevier, 1981)
(Paperback, North Holland, Amsterdam, 1987)

http://www.cs.ru.nl/~henk/
http://www.andrew.cmu.edu/user/cebrown/notes/barendregt.html

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


still has jump to fast entry point (ghc-5)

2005-11-24 Thread Malcolm Wallace
I know this will be going back a bit, but I have a problem with
compiling some code with ghc-5.04.3.  The same code goes through
ghc-6.2 with no problems, and until recently there were no problems
with ghc-5.04.3 either.  But a recent code change has caused the
following warning messages from ghc-5.04.3:

still has jump to fast entry point:
r4HK_entry:
leal12(%ebp), %eax
cmpl84(%ebx), %eax
jbe .L55
movl$r4HK_closure, %esi
movl-4(%ebx), %eax
.L56:
jmp *%eax
.L55:
movl4(%ebp), %esi
addl$12, %ebp
movl$r4HK_fast2, %eax
jmp .L56

There are about 350kb of very similar messages:

still has jump to fast entry point:
r3R_entry:
still has jump to fast entry point:
s4K3_entry:

and so on.

Does anyone have any idea what these mean, and how I might go about
fixing them?  Although they are only warnings, I'd like my software
to continue to be portable to older versions of ghc if possible.

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: recommended build system

2005-12-05 Thread Malcolm Wallace
Frederik Eaton [EMAIL PROTECTED] writes:

 I'm looking for a build system for my projects which will correctly
 handle all of ghc's dependencies. I.e. every time I ask it to rebuild
 an output file, it will only do the minimum amount of compilation
 necessary.

'hmake' is pretty good at what you want.
http://haskell.org/hmake

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Happiness! Re: New bug tracker: Trac

2005-12-06 Thread Malcolm Wallace
  I've imported all our SourceForge tracker data into a new Trac
  installation:

Just one minor nit: the front page URL tells me a lot about Trac,
but nothing at all about ghc!

Eventually, I worked out that I needed to click on View tickets,
but it took a while to realise this.

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Optimizations for mutable structures?

2005-12-07 Thread Malcolm Wallace
Jan-Willem Maessen [EMAIL PROTECTED] writes:

- Fetch elimination for imperative reads:
  writeIORef r e  acts  readIORef r
  === writeIORef r e  acts  return e

This transformation is valid only on single-threaded systems.
If there is any possibility of an IORef being shared across threads,
you are out of luck.

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Optimizations for mutable structures?

2005-12-07 Thread Malcolm Wallace
Simon Marlow [EMAIL PROTECTED] writes:

 I should have said that if 'acts' blocks, then the transformation is
 invalid.

Well that is exactly what I was assuming when I said that the
transformation is invalid.  In the general case, for some arbitrary
actions between the write and the read (excluding another write of
course), there is no guarantee that the IORef remains unmodified.

If you want to restrict the intermediate actions to be non-blocking,
such that another thread cannot run, then that is an extra (and
significant) proof obligation.

And AFAICS your non-blocking argument only applies to co-operative
scheduling.  If pre-emption is permitted (e.g. interrupt-handling),
then all bets are off, because an arbitrary thread could write to
the IORef at any moment.

 I don't think so.  Malcolm asserted that the transformation was invalid
 in a multi-threaded implementation; I disagree - it's just as valid in a
 multi-threaded implementation as a single-threaded one.

I think what I said was correct in general.  You need quite a lot of
side-conditions to assert the opposite.

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Optimizations for mutable structures?

2005-12-07 Thread Malcolm Wallace
[previously sent by mistake to Simon only - new para at end]

Simon Marlow [EMAIL PROTECTED] writes:

 Now, take the original program, but change the creation of m2 to
 newMVar (), i.e. m2 starts off full.  Is the transformation valid now?
 Well maybe, because in some interleavings acts does not block, and we
 can prove that at compilation time.

I don't think it is valid for a compiler to say that one possible
execution path permits me to remove some code, therefore I will remove
that code on all possible execution paths.

The example I had in mind was a GUI where the action
  writeIORef r e  acts  readIORef r
is intended to capture a situation where first we record some global
configuration data for the application, then permit some arbitrary GUI
actions to occur, and then we retrieve the configuration data again.

My expectation is that the config data /will/ have been changed by
some other GUI thread.  Surely it cannot be OK for the compiler to
silently deliver the original unchanged data here - it goes against
the programmer's intention.

Surely, if a Haskell programmer is going to write code that explicitly
reads from a reference after writing to it, that sequence must 9/10
be intentional: otherwise wouldn't she have just used a let-binding?

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Optimizations for mutable structures?

2005-12-09 Thread Malcolm Wallace
Simon Marlow [EMAIL PROTECTED] writes:

 In the general case, for some arbitrary
  actions between the write and the read (excluding another write of
  course), there is no guarantee that the IORef remains unmodified.
 
 This is an analysis that's performed all the time in C compilers, it's
 quite straightforward to do a good approximation.  One simple algorithm
 is: a store can be forwarded to a matching read as long as there are no
 intervening writes that may alias, or function calls.
 
 C does this and C has threads, so what's the difference?

There is a big difference between C variables and IORefs.  For one
thing, a C variable can have scope local to a procedure.  If so,
then the suggested transformation is entirely valid even in the
presence of threads, because no other thread is permitted access to
the local variable.

M[fp+offset(x)] - v
...
w - M[fp+offset(x)]
===
M[fp+offset(x)] - v
...
w - v

Global variables are more tricky, but I guess it is probably common
to permit the elimination of the 'read' there as well, even though
technically this is unsafe in the presence of threads.  My guess is
that this behaviour is the cause of a lot of thread unsafeness in
common C libraries however.

M[address(x)] - v
...
w - M[address(x)]
===
M[address(x)] - v
...
w - v

Haskell has neither local nor global variables in the same sense as C.

IORefs more closely resemble C pointers.  A pointer has indeterminate
lifetime and scope.  It can be passed around from procedure to
procedure, and from thread to thread.  There can be aliases to the
same memory location in multiple other contexts.  If I'm writing
a hardware driver, the pointer address might be memory-mapped to a
device register, in which case writing to that address and immediately
reading back from it may not be an identity.  I've certainly dealt
with devices where the same hardware port when written to, expects
control data, but when read from delivers status data.  So here:

M[M[x]] - v
...
w - M[M[x]]

it would be totally incorrect for the compiler to eliminate the read.

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: darcs switchover

2005-12-16 Thread Malcolm Wallace
Simon Marlow [EMAIL PROTECTED] writes:

 Malcolm, Ross - since you both also use the CVS libraries tree, is it
 going to be possible for you to switch to using darcs to get the
 libraries?  Any idea how long you'll need?

I've been looking at the cvs configuration file CVSROOT/modules.
I /think/ the procedure is something like changing this:

  nhc98src-d nhc98   nhc98
  nhc98libraries  -d nhc98/src/libraries fptools/libraries
  nhc98   -a nhc98src nhc98libraries

to this:

  nhc98src-d nhc98   nhc98
  nhc98libraries  -o darcs get --reponame=nhc98/src/libraries \
   http://cvs.haskell.org/darcs/libraries
  nhc98   -a nhc98src nhc98libraries

and then a fresh cvs checkout of the nhc98 would be required in
order to pick up the new location.  Has anyone else tried this kind
of tweak before and confirm that it is likely to work?  If not,
I might test it out with the smaller cpphs module initially.

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: darcs switchover

2005-12-19 Thread Malcolm Wallace
Ross Paterson [EMAIL PROTECTED] writes:
 
 No problem for me if you switch over at any time.  But how about having
 a separate repository for each library package?

Seconded.

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: darcs switchover

2005-12-20 Thread Malcolm Wallace
Simon Marlow [EMAIL PROTECTED] writes:

 The aim is to eventually switch over to using darcs for our revision
 control.  The point of this message is to find out what constraints
 people have that will affect when we can throw the switch.

One thing it occurs to me to ask is what will be happening to CVS
commit messages, once the switchover to darcs happens?

I have investigated this briefly, and it seems that darcs does not
yet directly support mailing out commit messages from a repository.
There is a wrapper script at
darcs get http://www.cse.unsw.edu.au/~dons/code/darcs-mail
but this requires administration privileges on the hosting machine,
since you need to rename the darcs binary proper, then install the
wrapper in its place.  Also, it is unclear to me whether this wrapper
works equally well in all situations, e.g. with 'darcs apply' on the
hosting machine, 'darcs push' from a separate repository on the same
host, or 'darcs push' from a remote machine with ssh.

Anyone sufficiently familiar with this to shed any light?

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: darcs switchover

2005-12-21 Thread Malcolm Wallace
[EMAIL PROTECTED] (Donald Bruce Stewart) writes:

  One thing it occurs to me to ask is what will be happening to CVS
  commit messages, once the switchover to darcs happens?
 
 I originally wrote this script as a temporary fix until darcs supported
 post-apply hooks. If it does now, perhaps there's no need for the
 wrapper, and instead a mail program can be invoked by darcs itself as a
 hook (i.e. just the core of darcs-mail can be `hooked').

Ah, yes I have just upgraded to darcs 1.05 (from 1.03), and there
are posthooks available for every command now.  However, there is
one wrinkle that means we can't use a stripped-down version of your
darcs-mail script directly.  The command invoked by the posthook does
not, AFAICS, get to look at the patch bundle.  This means the posthook
can only report a single patch per bundle, something like this:

darcs changes -s --last=1 | mail -s darcs commit `cat mailinglist`

where previously, the --last argument could in fact determine a fully
accurate count of patches contained in the bundle.  I'm not sure from
the documentation whether multiple patches are normally submitted
simultaneously from one repository to another, but I suspect the
answer is yes.  Any ideas?

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: darcs switchover

2005-12-23 Thread Malcolm Wallace
Simon Marlow [EMAIL PROTECTED] writes:

  But how about having a separate repository for each library
  package? 
 
 The time to mention this would have been a few weeks ago when I proposed
 the current scheme :-)

Err, I think I did...

 I think it /would/ actually be nicer to split up the repository into
 separate packages.  However, of the two ways to do this that John
 mentioned, only the second is practical IMO - that is, generate the
 repositories from CVS.  So it's entirely up to John whether he wants to
 put the effort in or not.

Is there more to this job than just running either cvs2darcs or tailor,
then waiting a few days (:-) for it to finish?

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: darcs switchover

2006-01-09 Thread Malcolm Wallace
Sven Panne [EMAIL PROTECTED] writes:

  I've been looking at the cvs configuration file CVSROOT/modules.
  I /think/ the procedure is something like changing this:
 
nhc98src-d nhc98   nhc98
nhc98libraries  -d nhc98/src/libraries fptools/libraries
nhc98   -a nhc98src nhc98libraries
 
  to this:
 
nhc98src-d nhc98   nhc98
nhc98libraries  -o darcs get --reponame=nhc98/src/libraries \
 http://cvs.haskell.org/darcs/libraries
nhc98   -a nhc98src nhc98libraries
 
  and then a fresh cvs checkout of the nhc98 would be required in
  order to pick up the new location.
 
 As already mentioned on the cvs-all list this morning, this does not 
 work... :-(

No?  I've tested it (using nhc98cpphs rather than nhc98libraries),
and it seems to work for me.  What is the problem?  (Of course, I'm
not trying to do a two-way synchronisation, just grafting a darcs
repo into the cvs tree.)

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: darcs switchover

2006-01-17 Thread Malcolm Wallace
 John Goerzen wrote:
  * I will re-convert all of the top-level directories in the current
libraries darcs repo, except for: doc, mk, and Cabal
  * Each new repo will be under darcs.haskell.org/packages

Inspired by the new browsable interface to the libraries repo at
http://darcs.haskell.org/darcsweb/
I have installed a similar darcsweb interface for the software
currently distributed through darcs at York:
http://www.cs.york.ac.uk/fp/darcs/
including cpphs, hoogle, yhc, Blobs and so on.

Meanwhile, I noted that the HaXml repo on darcs.haskell.org seems
to be a verbatim copy of the darcs repo at York.  This this right?
I was slightly disappointed, since I think I made a bit of a mess of
the CVS - darcs conversion of HaXml, and was secretly hoping that when
the fptools conversion happened, it would make a cleaner job of it,
based on the full CVS history...  Just wondering?

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: darcs switchover

2006-01-18 Thread Malcolm Wallace
John Goerzen [EMAIL PROTECTED] writes:

  Meanwhile, I noted that the HaXml repo on darcs.haskell.org seems
  to be a verbatim copy of the darcs repo at York.
 
 Ahh.  You are correct.
 
 Re-converting now, since you've presumably committed patches to the
 darcs side, is probably not going to be practical.

Actually, the way I have been working is to commit changes to CVS
first, then to (forget to) propagate them into darcs.  AFAIK, the
two repositories are in synch right now, but if there is ever any
discrepancy, I always treat the CVS one as correct.

Thus, now would be an excellent time to re-convert, and I would
then throw away my own darcs repo and switch to treating the
darcs.haskell.org repo as the master.

I can't remember where the rest of the ghc conversion process has
reached - is it also about ready to switch over to darcs-as-master yet?

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GHC vs. GCC on raw vector addition

2006-01-18 Thread Malcolm Wallace
Sven Moritz Hallberg [EMAIL PROTECTED] writes:

 I'm running GHC and GCC head-to-head on the task of adding a bunch of
 long IOUArray-Vectors really fast. My machine is a Linux-ppc PowerBook
 and gets a runtime for the GHC-compiled binary that's about 10x as long
 as for GCC.

Is it possible that gcc is making use of the ppc AltiVec instructions,
and ghc is not?

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GHC 6.5 on Mac Os X

2006-03-30 Thread Malcolm Wallace
Chris Brown [EMAIL PROTECTED] writes:

 ld: Undefined symbols:
 _TypeRep_AClass_stauic_info

I have noticed that there are spelling mistakes in these error messages.

  _TypeRep_AClass_stauic_info
should be
  _TypeRep_AClass_static_info

Earlier there was something with
DISCASD
instead of
DISCARD

If you are cutting and pasting these error messages (rather than typing
them by hand), then this strongly suggests a faulty low bit in memory.

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [Haskell] GHC Hackathon

2006-05-23 Thread Malcolm Wallace
  I think many would be grateful if a podcast were made of this event
  such that those who missed it can still watch the presentations.
 
 +1. A podcast would be perfect, posting minutes would be next in line.

If the Hackathon goes ahead, recording a video podcast of the event
should be straightforward.  (I've been playing with streaming web media
lately, and can volunteer to do that side of things.  The quality can be
surprisingly good.)  Mind you, even the compressed web streams will not
be small - approx 150Mb per hour.  A one day tutorial could easily
stretch to over 1Gb.

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: -threaded

2006-07-07 Thread Malcolm Wallace
Christian Maeder [EMAIL PROTECTED] wrote:

 It doesn't work under solaris and under linux [1] my nightly
 compilation jobs are killed every tuesday morning (!) for some
 reason that i cannot reproduce. I suspect the threaded RTS and heavy
 load. I had no such problems with ghc-6.4.1 before.

A process can be Killed by the operating system if the machine runs
out of virtual memory.  I suspect someone else is running a cron job on
Tuesdays that fills memory.  It is unlikely to be (only) ghc's fault.

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: RULES pragmas

2006-07-12 Thread Malcolm Wallace
[EMAIL PROTECTED] (Donald Bruce Stewart) wrote:

  So what am I doing wrong?  And is there any way to ask the compiler
  to give a warning if the RULES pragma contains errors?
 
 In this case, it's because it's missing -fglasgow-exts, I think.

Ah, thank you.  The missing (and undocumented) option.  Is there any
reason why -fglasgow-exts should be required?  Judging by the flag
reference material in section 4.17.15, -frules-off is used to turn RULES
off explicitly, but there is no corresponding flag to turn them on -
hence I assumed they would be enabled by default when -O or -O2 is set.

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: RULES pragmas

2006-07-12 Thread Malcolm Wallace
Malcolm Wallace [EMAIL PROTECTED] wrote:

 Ah, thank you.  The missing (and undocumented) option.

Actually, now I came to submit a patch to the manual, I discover that it
/is/ documented, but at the beginning of section 7.  (But on the index
page on the web, the link to section 7 is two whole screenfuls away from
the link to 7.10, so it is no wonder I didn't think to look there
first.)

Maybe there are other subsections of 7 that could usefully gain a
similar pointer to the need for -fglasgow-exts?  For instance, are other
pragmas (INCLUDE, INLINE, UNPACK) only activated by -fglasgow-exts?

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Lookup module and package defining x?

2006-07-21 Thread Malcolm Wallace
Marc Weber [EMAIL PROTECTED] wrote:

 My purpose: After having found the a function I want to use it without
 having to search where does it belong to and where does it come from.
 I want it beeing as up to date as the installed libraries.

You can download Hoogle as a command-line tool, and give it your
complete installed libraries to index.  Then it will be accurate for
your own setup.  Of course, you would need to manually update it every
time you install a new library.

 That's why I thought it might be best to integrate it into ghc?

This kind of tool, though useful, has almost nothing in common with the
compiler.  Although I suppose it would be useful if Hoogle could read
the ghc-pkg file format when indexing all locally-available modules.

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GHC compile times (was Re: GHC 6.4.3 is stalled)

2006-07-26 Thread Malcolm Wallace
Joel Reymont [EMAIL PROTECTED] wrote:

 Thanks for the tip! I'm _really_ interested in why it takes 55 min on 
 Linux and 3+ hours on Mac Intel, though. Any clues?

Building a compiler generally reads/touches/creates a very large number
of files.  So one possibility is the relative efficiency of the OS
filesystem implementation.  Apple's HFS+ is reputed to be fairly slow,
as are the Microsoft filesystems (VFAT, NTFS), at least compared to the
various unix-derived filesystems (UFS, ext2 etc).

I recall from a few years back that building nhc98 took twice as long
under Windows as under linux, on the very same machine, with the same
versions of boot-compilers.  The only major variable I could think of
at the time was VFAT vs ext2.

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GHC compile times (was Re: GHC 6.4.3 is stalled)

2006-07-26 Thread Malcolm Wallace
Joel Reymont [EMAIL PROTECTED] wrote:

 Thanks for the tip! I'm _really_ interested in why it takes 55 min on 
 Linux and 3+ hours on Mac Intel, though. Any clues?

Another thought.  The ghc HACKING guide has this to say:

The GHC build tree is set up so that, by default, it builds a
compiler ready for installing and using.  That means full
optimisation, and the build can take a *long* time.  If you unpack
your source tree and right away say ./configure; make, expect to
have to wait a while.

For hacking, you want the build to be quick - quick to build in the
first place, and quick to rebuild after making changes.  Tuning your
build setup can make the difference between several hours to build
GHC, and less than an hour.  Here's how to do it.

http://cvs.haskell.org/cgi-bin/cvsweb.cgi/~checkout~/fptools/ghc/HACKING?content-type=text%2Fplain

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Re[2]: [GHC] #876: stack overflow on 'length . filter odd $ [0 .. 999999999]'

2006-08-31 Thread Malcolm Wallace
Bulat Ziganshin [EMAIL PROTECTED] wrote:

   It makes sense to me that the above behaviour is seen: length is
   now a good
   consumer, but it generates 1+(1+(1+(1+... as it is consuming, and
   this causes a stack overflow. I don't think we can fix this while
   staying with fold/build fusion, so it looks to me like the patch
   should be reverted and the whole problem looked at post-6.6.
 
 in general, for any function we can either implement
 1) good consumer based on using foldr
 2) tail-recursion
 
 are you agree?

I'd like to point out that, if you are prepared to abandon foldr/build
fusion in favour of hylo fusion, you can code good consumers using
either foldr or foldl.  (Length is a foldl, because it uses an
accumulator.)  Foldl is tail-recursive, but this does not prevent it
being a good consumer, provided your framework of fusion laws is
sufficiently flexible.

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: cvs commit: hugs98 Makefile RPM.mk hugs98/libraries/tools convert_libraries

2006-09-05 Thread Malcolm Wallace
 HaXml (no longer builds)
  
  In what way does HaXml fail to build for Hugs?  Is it easily
  fixable?
 
 ... and there's the famous Data.FiniteMap.

So does anyone have any objections if I go ahead and commit the
replacement (compatibility) implementation of Data.FiniteMap to the main
repository for packages/base?

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: FiniteMap

2006-09-05 Thread Malcolm Wallace
  So does anyone have any objections if I go ahead and commit the
  replacement (compatibility) implementation of Data.FiniteMap to the
  main repository for packages/base?
 
 I'd rather see HaXml updated to use Data.Map, perhaps with a
 compatibility layer for older GHCs.

OK, I've looked more closely at all uses of Data.FiniteMap in HaXml, and
they are far from critical, so have reverted them to using simpler
lookup structures.

As far as I can tell, none of my other software now depends on FiniteMap
either, so I withdraw the threat to resuscitate it.  (Sorry Duncan!)

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Debugging on Mac OS X

2006-10-24 Thread Malcolm Wallace
Luke Worth [EMAIL PROTECTED] wrote:

 I just installed GHC 6.6 using the PPC binary installer on Mac OS X.  
 I'm having some trouble getting debuggers to work; I have tried both  
 plargleflarp (buddha) and Hat. Neither of them will compile on GHC  
 6.6 on Mac yet.

As an interim measure, I have just made available a 'snapshot' release
of Hat-2.05, specifically to ensure that it compiles with ghc-6.6.  This
is very much a stop-gap.  There have been huge changes in the standard
base library package since the last full release of Hat, which are not
reflected in 2.05.  (For example, Parsec and Data.FiniteMap are no
longer in base, whilst Data.Map, Data.Set and so on have been added.
Hat still has the older API.)

The Hat team is planning to rectify these problems shortly, but we are
unlikely to be able to make a full release before the end of the year.
I hope the 2.05 release is sufficient to meet at least some people's
needs in the meantime.

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: seq vs. pseq

2006-10-27 Thread Malcolm Wallace
Simon Marlow [EMAIL PROTECTED] wrote:

 The difference is subtle.  The semantics of seq and pseq are
 identical; however,  GHC can see that seq is strict in both its
 arguments and hence could choose to  evaluate them in either order,
 whereas pseq is only strict in its first argument  as far as the
 strictness analyser is concerned.  The point is that pseq is  useful
 for controlling evaluation order, which is what you want for adding 
 parallelism to a program.  seq, on the other hand, is not useful for
 controlling  evaluation order.

This is a rather weird thing, and I would consider it a bug in the
Haskell Report, rather than a bug in ghc.  (It bites hard when you are
trying to implement something like HPC.)

The very name 'seq' surely suggests that you are controlling the
evaluation order.  Please evaluate this thing on the left first.  But
that is _not_ what the Haskell Report says!  Ghc takes the Report
literally, and so the thing on the right is just as likely to be
evaluated before the thing on the left!

Surely the language designers did not intend this consequence.  For
Haskell-prime, can we fix this bug, and ensure that 'seq' really implies
ordering of evaluation?

[ If you just want strictness annotations, with the compiler free to
  reorder computations, I would say ($!) is a better bet, and could be
  redefined to use not the natural `seq`, but the strict-in-both-arguments
  variation. ]

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: OpenGL failing with Mac Intel 6.6 distribution

2006-10-31 Thread Malcolm Wallace
Deborah Goldsmith [EMAIL PROTECTED] wrote:

 I checked and the Mac OS X PowerPC binary distribution does not have  
 this problem; only Mac OS X Intel.

Is it possible that the Intel distro built the OpenGL package using
Cabal, but the PowerPC distro used Makefiles?  I seem to recall there
was some issue with Cabal failing to copy C header files to the final
installed location?

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: seq vs. pseq

2006-11-06 Thread Malcolm Wallace
Simon Marlow [EMAIL PROTECTED] wrote:

 The report is in general very careful to say absolutely *nothing*
 about  evaluation order, leaving the implementation free to choose,

Yes, this is a highly desirable goal.

 However, having said all that, arguably an exception should be made in
 this  case.  The main use of seq (and strictness annotations) is to
 control  operational behaviour, rather than to change the semantics of
 the program

Indeed, `seq` is widely viewed as a wart on the language _because_ it
specifies the evaluation order, which is something otherwise avoided in
the Report.

So the doubly bizarre thing is that, actually, `seq` does not control
the evaluation order (which is the only valid reason for wanting to use
it in the first place), but nevertheless it undesirably changes the
semantics of programs such that equational reasoning no longer holds.

I think if we are going to allow ourselves the luxury of semantic
breakage, it should at least be worth the cost - we should get some
real and definite operational control in return.

That is why I think this:

 the evaluation-order  property of seq should be a strong hint, not a
 requirement - otherwise we fall  into the trap of mandating evaluation
 order.

is not strong enough.  `seq` should guarantee sequential evaluation.  If
you want a strong (but not mandatory) hint to the compiler about
strictness, than that should be a different construct at the user level.
At the moment, these alternatives are named `pseq` and `seq`.  One
suggestion is just to reverse their sense.  Another is to use bang
patterns for hints.  Another might be to introduce strictness hints in
type signatures.

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


  1   2   >