Bug in GHC - black holing

2000-04-07 Thread Andy Gill



In GHC, 4.07:

module Main where
main = print (let x = x in x :: ())

With the latest CVS srcs, on WinNT, crashes with

main.exe: fatal error: schedule: invalid what_next field

It looks like the lazy black holing failing to correct
put the thread on the relevant queue.
(quote for code:
  /* don't need to do anything.  Either the thread is blocked on
   * I/O, in which case we'll have called addToBlockedQueue
   * previously, or it's blocked on an MVar or Blackhole, in which
   * case it'll be on the relevant queue already.
   */
) 

I just spend several hours trying to track down this
problem, thinking it was a STG Hugs bug :-(.
Several things are gated on this getting fixed, esp.
making the STG Hugs Threads/Exceptions library more robust.

Cheers!

Andy




[dongen@cs.ucc.ie: Re: Debugging techniques]

2000-04-07 Thread Marc van Dongen

Sorry about this. I forgot to group reply.


- Forwarded message from Marc van Dongen [EMAIL PROTECTED] -

Date: Fri, 7 Apr 2000 09:55:12 +0100
From: Marc van Dongen [EMAIL PROTECTED]
To: "Michael A. Jones" [EMAIL PROTECTED]
Subject: Re: Debugging techniques
X-Mailer: Mutt 1.0.1i
In-Reply-To: [EMAIL PROTECTED]; from 
[EMAIL PROTECTED] on Thu, Apr 06, 2000 at 03:05:23PM -0700

Michael A. Jones ([EMAIL PROTECTED]) wrote:

: Well, I tried the trace function as was recommended, linking in IOExts and
: all, but I get the following error when I run the application:
: 
: main: fatal error: No threads to run!: Deadlock?
: 
: The statement where it is used is:
: 
: datalogQueryHistogramResult = IOExts.trace "here"
: (processStaticHistogramQuery  datalogQuery datalogQueryRequest2
: datalogQueryFilter6)
: 
: testDatalogQuery = 
:   putStrLn (show (firstPageOfHistogramData
: datalogQueryHistogramResult)) 
: 
: Any ideas how to deal with this problem?

Hi Michael,


This is really a big problem. I have been strugling with it
myself. The safest thing to do is to use `error' (sad but
true). That's the only thing I can recommend:-(


Regards,


Marc van Dongen
-- 
 Marc van Dongen, CS Dept | phone:   +353 21 903578
University College Cork, NUIC | Fax: +353 21 903113
  College Road, Cork, Ireland | Email: [EMAIL PROTECTED]

- End forwarded message -

-- 
 Marc van Dongen, CS Dept | phone:   +353 21 903578
University College Cork, NUIC | Fax: +353 21 903113
  College Road, Cork, Ireland | Email: [EMAIL PROTECTED]




NameSupply module

2000-04-07 Thread trb

Why has the NameSupply module been dropped from the ghc libraries (there are now
two slightly different implementations: one in green-card and one in hdirect) ? 
Can we please have one standard name supply library ?

While we're at it, shouldn't Name be an opaque type (i.e. a newtype) that is an
instance of Eq and has no other operations ? I wrote a module NameSupplyEx.hs
to do this, but now it will not compile because the NameSupply module has gone:


module NameSupplyEx (
   NameSupply, initialNameSupply, splitNameSupply, getName, listNameSupply, Name   

   ) where
import NameSupply hiding ( Name, getName )
import qualified NameSupply as N

newtype Name = MkName N.Name

instance Eq Name where
   (MkName x) == (MkName y) = x == y

getName :: NameSupply - Name
getName = MkName . N.getName


Tim




Strictness info in interface files

2000-04-07 Thread trb

The ghc user's guide says:

 How do I find out a function's strictness?

 Don't guess-look it up.

 Look for your function in the interface file, then for the third field in
 the pragma; it should say _S_ string. The string gives the strictness
 of the function's arguments. L is lazy (bad), S and E are strict (good),
 P is "primitive" (good), U(...) is strict and "unpackable" (very good),
 and A is absent (very good).

So I compiled a module with -O and looked at the line interface file for a
particular function. I get things like:

1 maybeToBool :: __forall [a] = PrelMaybe.Maybe a - PrelBase.Bool {-## __A 1
__C __S S __U (\ @ a s1 :: (PrelMaybe.Maybe a) - case s1 of wild {
PrelMaybe.Nothing - PrelBase.False; PrelMaybe.Just x - PrelBase.True }) ##-} ;

1 merge :: __forall [a] = [[a]] - [a] {-## __A 1 __C __S S __U (\ @ a s1 ::
[[a]] - lvl1 @ a (List.transpose @ a s1)) ##-} ;


I can't see the _S_ string bit . Has the documentation rotted, and what is the 
real truth ?

Tim




ghc library mechanisms

2000-04-07 Thread trb

ghc appears not to have any mechanism for the user to specify the full path of a
library. For example, gcc accepts

 gcc main.c /home/fred/lib/libfoo.a

in place of the more usual

 gcc main.c -L /home/fred/lib -lfoo

whereas ghc only accepts the latter. I read carefully through the options in the 
User's Guide, but could not see anything suitable.

I have a makefile system where make locates the libraries. This allows make to
have the full path of the library, so it can express dependency of programs on
the libraries they are linked against. I want to use the system with ghc (in
fact that is its main purpose).

I suppose I could kludge it for ghc by getting make to split up the library
paths into directory and library components and then feeding them into the -L/l
options, but how about an option for specifying the full path to a library ?

(Of course, I should try to stop ghc quietly picking up standard libraries, so as
to capture dependencies on them, but that is not so important. The main need
is to catch the cases (common with developer libraries) where the implementation
of a library has changed (e.g. to fix a bug), but not its interface. When
standard libraries change, their interfaces are very likely to change as well.)

Tim




ghc with shared libraries ?

2000-04-07 Thread trb

Does ghc support building and using shared libraries nowadays ? If so, what is
the recommended approach (on Linux in particular) ?

Last time I tried it (3 years ago), the result was an executable that dumped
core.

Tim




Re: string to Integer

2000-04-07 Thread Jon Fairbairn

 Then, the question is why we write
   result = function operand1 operand2
 instead of
   operand1 operand2 function = result
 
 I actually think the latter is cooler.  :)

I think there may be cultural influences about word order and/
or writing direction creeping in here :-)
-- 
Jón Fairbairn [EMAIL PROTECTED]
18 Kimberley Road[EMAIL PROTECTED]
Cambridge CB4 1HH+44 1223 570179 (after 14:00 only, please!)






Re: string to Integer

2000-04-07 Thread George Russell

Jon Fairbairn wrote:
 
  Then, the question is why we write
result = function operand1 operand2
  instead of
operand1 operand2 function = result
 
  I actually think the latter is cooler.  :)
 
 I think there may be cultural influences about word order and/
 or writing direction creeping in here :-)
There are mathematicians who put the function after its argument.
But I'm pretty sure they are in the minority.




Re: string to Integer

2000-04-07 Thread Frank Atanassow

Yuichi Tsuchimoto writes:
   Or look at o's and flippo's types:
   
(.)  :: ((a - b) - (c - a)) - (c - b)
flip (.) :: ((a - b) - (b - c)) - (a - c)
   
   Surely the second one is much cooler!
  
  Yes, indeed!
  
  Then, the question is why we write
result = function operand1 operand2
  instead of
operand1 operand2 function = result

As a question of notation, I think the difference is that you use the
diagrammatic notation (flip (.)) when you want to emphasize the process of
computing something (buzzword, "imperative"). If you read left-to-right then
you can see each stage of a transformation, in the order which it "logically"
occurs. On the other hand, the (.)-style notation emphasizes the declarative
viewpoint since, again reading left-to-right, you start with what you want
and refine down to what you're starting with.

In category theory one often writes commutative arrow diagrams to express
systems of equations. If you use the diagrammatic notation, it can be simpler
to follow paths in the diagram because, by convention, one prefers right- and
down-pointing arrows over left- or up-pointing ones.

If Haskell 98 had user-definable infix type expressions (and - wasn't part of
the syntax already), you could define the transpose of (-)

  type b - a = a - b

and then write the signature for (.) as follows:

  (c - a) - (c - b) - (b - a)

Using - in type signatures has the advantage that the first thing you see in
a signature is what is produced, rather than what is necessary to produce,
which is sometimes what you want when you have a set of algebraic functions
like John Hughes' pretty-printing library:

 text  :: Doc - String
 (+) :: Doc - Doc - Doc

However it does not work so nicely in Haskell since by convention we curry
everything, so the order of arguments is also reversed. If we used uncurried
functions more often the signature for cons

  cons :: List a - List a - a

would be more intuitive:

  cons :: List a - (a, List a)

(Incidentally, I think Roland Backhouse made this argument, i.e., that we
should prefer (-) to (-), although he was working with a relational calculus
rather than a functional one.)

-- 
Frank Atanassow, Dept. of Computer Science, Utrecht University
Padualaan 14, PO Box 80.089, 3508 TB Utrecht, Netherlands
Tel +31 (030) 253-1012, Fax +31 (030) 251-3791





Re: string to Integer

2000-04-07 Thread Frank Atanassow

Frank Atanassow writes:
  Using - in type signatures has the advantage that the first thing you see in
  a signature is what is produced, rather than what is necessary to produce,
  which is sometimes what you want when you have a set of algebraic functions
  like John Hughes' pretty-printing library:
  
   text  :: Doc - String
   (+) :: Doc - Doc - Doc

On re-reading this I see my point was not so clear. What I wanted to indicate
is that the functions of an algebra have a common codomain, like Doc, so
putting it first in a signature emphasizes the commonality between
them. Combinator languages and monads (the extra operations are generally
typed as X - M Y, for a monad M) are pretty common in Haskell, so by that
token (-) might be preferable to (-).

OTOH, if we used coalgebras more heavily in Haskell we could make the opposite
case, that (-) is preferable, since coalgebras have a common domain.

-- 
Frank Atanassow, Dept. of Computer Science, Utrecht University
Padualaan 14, PO Box 80.089, 3508 TB Utrecht, Netherlands
Tel +31 (030) 253-1012, Fax +31 (030) 251-3791





RE: Die Meisterstu:cke of software engineering

2000-04-07 Thread Erik Meijer

Hi,

I must admit that I got carried away by new extension, and have not
come around to making a new release yet.

   On Oct. 4, 1999, I enquired here about availability
   of software described in that paper (Where is "Server
   Side Scripting" code?) and Erik's answer was, loosely
   speaking, "wait until I finish it". As far as
   I can tell nothing has changed in this respect.

Probably you missed the announcement of mod_Haskell some time ago.
Anyway, mod_Haskell gives you a Haskell98 update of my CGI-library
integrated into Apache (yes, yes, that Linux-based webserver :-)

At the same site http://losser.st-lab.cs.uu.nl:8080/ you will
also find a pre-releas of Haskell Server Pages (HSP). Similar
to ASP, JSP, PHP, PSP, etc it allows you to embed scripts
directly inside HTML pages, but in addition you can recursively
embed HTML inside HSP scripts. For example you can write

%
cells = 
  [ [ (x,y) | x - [1..16] ]
  , y - [1..16] 
  ]

genData = \c -
  td bgcolor=% genColor c %
% c %
  /td
  
genRows = map (\r - tr% map genData r %/tr)
%

html
body
  table border="1"
% genRows cells %
  /table
/body
/html

HSP are translated by a simple pre-processor to a "normal"
CGI script. The great thing is that as a programmer
you don't have to mess around with some (arbitrary)
encoding of HTML. You just write *concrete* HTML syntax.

HSP is a proof of concept for the viability of XMLambda
(http://www.cse.ogi.edu/~mbs/pub/XMLambda.ps.gz, regrettably 
it was rejected for USENIX) which generalizes this to XML, so
that you can define your own DTD and construct, transform,
and pattern match XML documents using concrete syntax as well.
Much better than XSL.

Erik

PS

There is also a installshield Haskell98 compatible
version of my library intended for IIS (the MS
webserver) that includes a version of
the JFP paper in HTML-help format. Unfortunately
the student who made this left before he perfected
the install script so you need to tweak a few 
things by hand.





Thanks (I hope it works this time).

2000-04-07 Thread Juergen A. Erhard

-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

Thanks for all the friendly mail... I have resub'd now, and I hope I
stay that way.

Bye, J

PS: This is also a test mail... if the list is set to send copies of
one's own mail, I'll get a copy of this.  That'd be great... otherwise
I have to wait a couple hours to be sure... 5 or 6 mails a day is
about one every 4 hours...

- -- 
Jürgen A. Erhard  eMail: [EMAIL PROTECTED]  phone: (GERMANY) 0721 27326
 MARS: http://members.tripod.com/Juergen_Erhard/mars_index.html
"Ever wonder why the SAME PEOPLE
  make up ALL the conspiracy theories?" -- Michael K. Johnson
-BEGIN PGP SIGNATURE-
Version: GnuPG v1.0.1 (GNU/Linux)
Comment: Use Mailcrypt and GnuPG http://www.gnupg.org/

iEYEARECAAYFAjjuHaEACgkQN0B+CS56qs2UYQCfW+jLkQNP+FNezAF/z8IP6CrE
8ZAAn0Ft6PVM46fldaadvYnX/hfOobyf
=WnsG
-END PGP SIGNATURE-




Re: Die Meisterstu:cke of software engineering

2000-04-07 Thread Eelco Dolstra

On Fri, 7 Apr 2000 16:23:30 +0200, Erik Meijer [EMAIL PROTECTED] wrote:

 [CGI programming with HSP]
  At the same site http://losser.st-lab.cs.uu.nl:8080/ you will
  also find a pre-releas of Haskell Server Pages (HSP). 

It should be mentioned that the pre-release (contained in
mod_haskell.0.2pre1) on the mod_haskell site is a rather ancient and
primitive version.  For example, it didn't yet support the recursive
nesting of Haskell code and XML that Erik mentioned.  A new release should
make it to the website Real Soon Now.

Meanwhile, you can grab the latest sources at

  http://losser.st-lab.cs.uu.nl:8080/services/cvsweb-mod_haskell/hs/hsp/

Regards,

Eelco.

-- 
The worst thing about fancy data types is that you have to declare them,
and Real Programming Languages, as we all know, have implicit typing based
on the first letter of the (six character) variable name.
   -- Ed Post, "Real Programmers Don't Use Pascal"




Re: string to Integer

2000-04-07 Thread Marcin 'Qrczak' Kowalczyk

Thu, 06 Apr 2000 22:23:10 +0200, Ralf Muschall [EMAIL PROTECTED] pisze:

 And if I call the label on the stones "integer_from_string"
 and "integer_from_intlist", unflipped (.) does as well.

In OCaml such functions are called int_of_string etc.

-- 
 __("Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/  GCS/M d- s+:-- a23 C+++$ UL++$ P+++ L++$ E-
  ^^  W++ N+++ o? K? w(---) O? M- V? PS-- PE++ Y? PGP+ t
QRCZAK  5? X- R tv-- b+++ DI D- G+ e h! r--%++ y-





RE: Die Meisterstu:cke of software engineering

2000-04-07 Thread Jan Skibinski



On Fri, 7 Apr 2000, Erik Meijer wrote:

 Probably you missed the announcement of mod_Haskell some time ago.
 Anyway, mod_Haskell gives you a Haskell98 update of my CGI-library
 integrated into Apache (yes, yes, that Linux-based webserver :-)

No I did not. What I missed is that mod_Haskell does
contain the upgraded version of CGI library, which
is based on your paper I cited in my previous post.

I looked at mod_Haskell before, I even recompiled
the Apache server, but it failed miserably during
the startup (the first frightful sign was that the memory
usage reports went out of bounds - I suddenly became
the owner of billions of megabytes).
I do not know the reason yet, but I am a bit reluctant
to try it again. There was probably some installation
error I made, but yet.. 
I'll give it a try again in the future, but 
.. thank you, I will stay with fastCGI idea for now.
This was the reason that I have not taken a good
look inside the mod_Haskell to find more about CGI.hs.

I owe you my thanks for this new version of CGI
library. However, that does not invalidate two
points that I made in my previous post:

+ Give us all a clear picture of current status of CGI.
  Available information on haskell.org pages is misleading.
  Make it clear (on your pages or wherever) that CGI.hs
  is upgraded and that it can be used in the classic way
  -- without fiddling with Apache. You see, you even
  did not make it clear in your last post here.

+ My second point was about lack of cooperation
  between different parties. If Andy's library
  is of any value (and I believe, it is) someone
  should make some concessions in here to make
  those two pieces compatible. We should work
  together towards common goals. I might be
  a bit naive here, though.. :-)

As for the XMLambda - it looks very interesting,
and I am sure I'll find some use for it later.   

Regards,
Jan






lst[x]

2000-04-07 Thread Sitzman

Hey all.. I imagine this is probably a silly question, but I was
wondering, is there a getElementAt function (or operator) that will return
the nth element in a list?
ie say I had a list called lst... I would like to say lst[2] and get back
the 2nd or third actually element in that list...

or, alternatively, to have getElementAt lst 2 would be okay too..

Thanks much!






Re: lst[x]

2000-04-07 Thread Sitzman

Disregard that.. found it ;-) !! :
Thx though