Program won't go away!

2000-10-18 Thread George Russell

In the GHC document, section "GHC-specific concurrency issues", it says:
 In a standalone GHC program, only the main thread is required to
   terminate in order for the process to terminate. 
I have a program (which does some fairly complex things with forking processes,
calling sockets etcetera) for which this doesn't appear to be true.  Specifically, the
very last line of the "main" action is:
  putStrLn "Test completed"
The program prints "Test completed", but then hangs.  I am using
the ghc-4.08.1 binary release on Linux.  What is going on.

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



Re: Program won't go away!

2000-10-18 Thread Marcin 'Qrczak' Kowalczyk

Wed, 18 Oct 2000 16:32:21 +0200, George Russell [EMAIL PROTECTED] pisze:

  In a standalone GHC program, only the main thread is required to
terminate in order for the process to terminate. 
 
 I have a program (which does some fairly complex things with forking processes,

The above fact applies to threads (module Concurrent), not processes
(module Posix).

In some sense it does apply to processes, but the interface of
forkProcess allows to "continue execution" with the child process,
while the main process (parent) waits somewhere.

 the very last line of the "main" action is:
   putStrLn "Test completed"
 The program prints "Test completed", but then hangs.

Quite possible. For example (untested):

main = do
pid - forkProcess
case pid of
Nothing - return () -- This is the new process.
Just _  - do
-- This is the old process.
sleep 100; exitWith ExitSuccess
-- This is the new process.
putStrLn "Test completed"

-- 
 __("  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


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



GHC for RedHat 7.0 (gcc 2.96)

2000-10-18 Thread Manuel M. T. Chakravarty

GHC (4.08.1) rpm packages for RedHat 7.0 are available from

  ftp://ftp.cse.unsw.edu.au/pub/users/chak/jibunmaki/i386/ghc-4.08.1-2.i386.rpm
  ftp://ftp.cse.unsw.edu.au/pub/users/chak/jibunmaki/i386/ghc-prof-4.08.1-2.i386.rpm

[The second package is only required for profiling.]

The corresponding source rpm is at

  ftp://ftp.cse.unsw.edu.au/pub/users/chak/jibunmaki/src/ghc-4.08.1-2.src.rpm

** IMPORTANT **

For this to work, you have to additionally install on old
version (2.0) of the GNU Multiprecision Library (GMP).  Get
it off your old RedHat 6.2 CD or alternatively from

  
ftp://ftp.linux.com/mounts/u2/mirrors/redhat/up2date/rhl-6.2/i386/RedHat/RPMS/gmp-2.0.2-13.i386.rpm
  
ftp://ftp.linux.com/mounts/u2/mirrors/redhat/up2date/rhl-6.2/i386/RedHat/RPMS/gmp-devel-2.0.2-13.i386.rpm

* You have to install *both* packages.

* They can co-exist with the new library (version 3.0)
  installed by default with RedHat 7.0.

NOTE: These packages cannot be installed on RedHat 6.2 and
  earlier (unless you manually upgrade to the rpm
  package manager 4.0).

Happy Hacking,
Manuel

PS: Could these packages be linked from GHC's download page?
And please also add the comment and links re gmp 2.0.
Moreover, please *don't* remove the old links for the
benefit of RH6.2 users.

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



Socket.hs problem under Windows 2000

2000-10-18 Thread Martijn

Hi,

I'm trying to set up some socket connections with Haskell on a Windows 2000 
platform, but I can't seem to get them working.

My program is rather simple:
--
import Socket

main = do { socket - listenOn (PortNumber 1234)
   ; return ()
   }
--

I know this shouldn't do anything at all, but instead it gives an error 
message:

Fail: does not exist
Action: getProtocolByName
Reason: no such protocol entry

I get the same message for any socket operation I try to perform. Also a 
basic call like getHostName from module BSD does not work. I've compiled 
with ghc version 4.05 with option "-syslib misc"

Should I compile differently, is this a problem with CygWin, or am I 
overlooking something?

TIA,
Martijn Schrage


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



RE: Socket.hs problem under Windows 2000

2000-10-18 Thread Sigbjorn Finne


You need to init WinSock first, i.e.,

  main = withSocketsDo $ do {...}

--sigbjorn

Martijn [mailto:[EMAIL PROTECTED]] writes:
 
 Hi,
 
 I'm trying to set up some socket connections with Haskell on 
 a Windows 2000 
 platform, but I can't seem to get them working.
 
 My program is rather simple:
 --
 import Socket
 
 main = do { socket - listenOn (PortNumber 1234)
; return ()
}
 --
 
 I know this shouldn't do anything at all, but instead it 
 gives an error 
 message:
 
 Fail: does not exist
 Action: getProtocolByName
 Reason: no such protocol entry
 
 I get the same message for any socket operation I try to 
 perform. Also a 
 basic call like getHostName from module BSD does not work. 
 I've compiled 
 with ghc version 4.05 with option "-syslib misc"
 
 Should I compile differently, is this a problem with CygWin, or am I 
 overlooking something?
 
 TIA,
 Martijn Schrage
 

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



Num class

2000-10-18 Thread Koen Claessen

Hi all,

For years I have wondered why the Num class has the Eq class
and the Show class as super classes.

Because of this, I cannot make functions an instance of Num
(becuase they are not in Eq or Show). Or a datatype
respresenting an infinite amount of digits (because Eq would
not make any sense).

Now I have found out the reason!

However, it does not make me happy, it makes me even more
sad.

It is of the defaulting mechanism of course! The defaulting
mechanism works as follows: If there is an unresolved
overloading error on a type variable a, which has as an
*only* constraint (Num a), then we take a to be the suitable
default.

If Show were not a super class of Num, the following program
would generate an error:

  main = print 42

If Eq were not a super class, the following program would
not work:

  main = print (if 42 == 42 then "koe" else "apa")

These programs are all fixed by inserting Show and Eq as
super classes of Num. So that one does not even notice!

Until now.

I am interfacing to an external library that uses
double-precision floating points internally for all numbers.
This is to be as general as possible. However, I know that
when I put for example an Integer in, I get one out too.
Thus, I want to give a Haskell interface that can deal with
this by any numeric type. So I define a type class:

  class Num a = Number a where
convertToDouble   :: a - Double
convertFromDouble :: Double - a

(somehow the Haskell numerical hierarchy does not even let
me define general functions that do this! -- but that is
besides the point.)

  instance Number Int
  instance Number Integer
  instance Number Float
  instance Number Double
  ...

All my library functions now have the shape:

  libraryFunction :: Number a = ... a ...

Where as actually:

  primLibraryFunction :: ... Double ...

And now the bad thing... When I use "libraryFunction" on a
numeric constant, such as 42, I get the error:

  ERROR "library.hs" (line 8): Unresolved overloading
  *** Binding : main
  *** Outstanding context : Number b

This is really annoying, and it is not clear why the default
mechanism works this way.

So here are my questions. Why does the default mechanism
have this restriction? I know that the default mechanism is
already broken (some desirable properties are destroyed) --
what properties will be broken by lifting this restriction?

/Koen.

--
Koen Claessen http://www.cs.chalmers.se/~koen 
phone:+46-31-772 5424  mailto:[EMAIL PROTECTED]
-
Chalmers University of Technology, Gothenburg, Sweden


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



pronunciation of =

2000-10-18 Thread Scott Turner

Is there a common way to pronounce "=" in discussions or when teaching?
I've learned all my Haskell from printed/visual documents.
--
Scott Turner
[EMAIL PROTECTED]   http://www.ma.ultranet.com/~pkturner

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



Re: pronunciation of =

2000-10-18 Thread Lars Lundgren

On Wed, 18 Oct 2000, Scott Turner wrote:

 Is there a common way to pronounce "=" in discussions or when teaching?
 I've learned all my Haskell from printed/visual documents.

How about 'bind'? and "" = 'then'.

/Lars L



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



Re: Num class

2000-10-18 Thread Marcin 'Qrczak' Kowalczyk

Wed, 18 Oct 2000 12:57:56 +0200 (MET DST), Koen Claessen [EMAIL PROTECTED] pisze:

 The defaulting mechanism works as follows: If there is an unresolved
 overloading error on a type variable a, which has as an *only*
 constraint (Num a), then we take a to be the suitable default.

This is not what the Haskell 98 Report says. Section 4.3.4:

"In situations where an ambiguous type is discovered, an ambiguous
type variable is defaultable if at least one of its classes is a
numeric class (that is, Num or a subclass of Num) and if all of its
classes are defined in the Prelude or a standard library (Figures 6--7
show the numeric classes, and Figure 5 shows the classes defined in
the Prelude.)"

I see no good reason for Show superclass of Num.

Eq makes a little more sense, but could be dropped too. It would be
inferred separately when a numeric literal is used in a pattern.

I agree that the default mechanism is ugly, and that at least the
restriction about classes defined in standard libraries should
be removed.

Clean has per-class defaults. I don't know how conflicting defaults
coming from different class constraints should be solved, or what about
multiparameter classes, and whether extending the defaulting mechanism
is a good idea at all. But since we don't have anything better...

-- 
 __("  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


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



RE: Num class

2000-10-18 Thread Mark P Jones

Hi Koen,

| If Show were not a super class of Num, the following program
| would generate an error:
| 
|   main = print 42
| 
| If Eq were not a super class, the following program would
| not work:
| 
|   main = print (if 42 == 42 then "koe" else "apa")
| 
| These programs are all fixed by inserting Show and Eq as
| super classes of Num. So that one does not even notice!

Your claims are incorrect.  Both of these examples type check
without any errors, and regardless of whether Show and Eq are
included as superclasses of Num.  It is easy to verify this
using "Typing Haskell in Haskell" (http://www.cse.ogi.edu/~mpj/thih);
I'll attach the script that I used for this below.  Put this in
the same directory as all the other .hs files and load it into
Hugs.  Then edit StdPrel.hs to remove the superclasses of cNum,
(replace [cEq, cShow] with []), and it will still work.

| For years I have wondered why the Num class has the Eq class
| and the Show class as super classes.
| 
| Because of this, I cannot make functions an instance of Num
| (because they are not in Eq or Show). Or a datatype
| representing an infinite amount of digits (because Eq would
| not make any sense).
| 
| Now I have found out the reason!

I don't think you have.

I do not know the reason either, but I suspect that it is largely
historical; when Haskell was first designed, the only types that
people wanted to put in Num were also equality and showable types.
By making Eq and Show superclasses of Num, types could sometimes
be stated more concisely, writing things like (Num a) = ... instead
of (Num a, Eq a, Show a) = ...

In the past ten years since the Haskell class hierarchy was, more or
less, fixed, we've seen several examples of types that don't quite
fit (Like functions, computable reals, etc. which might make sense
in Num but not in Eq).  A natural conclusion is that several of the
superclass relations between classes should be removed.  But realize
that there is an unavoidable compromise here: generality versus the
convenience of shorter types.  I suggest that there is no point on
the spectrum that would keep everybody happy all the time.

| It is of the defaulting mechanism of course!
| ...

Defaulting is a red herring in trying to understand why Show
and Eq are superclasses of Num.  Marcin has already pointed
out that your description of the Haskell defaulting mechanism
is not correct by quoting from the Haskell report.  You can
find another description, again based on the report, in the
thih paper.

| So I define a type class:
|   class Num a = Number a where
| convertToDouble   :: a - Double
| convertFromDouble :: Double - a
|... 
| All my library functions now have the shape:
|   libraryFunction :: Number a = ... a ...
| ...
| And now the bad thing... When I use "libraryFunction" on a
| numeric constant, such as 42, I get the error:
| 
|   ERROR "library.hs" (line 8): Unresolved overloading
|   *** Binding : main
|   *** Outstanding context : Number b
| 
| So here are my questions. Why does the default mechanism
| have this restriction? I know that the default mechanism is
| already broken (some desirable properties are destroyed) --
| what properties will be broken by lifting this restriction?

Defaulting only kicks in if (a) at least one class is numeric,
and (b) all classes are standard.  Number is not a standard
class (you just defined it yourself), so defaulting will not
apply.  Defaulting was designed to work in this way so that
(i) it would catch and deal with the most common problems
occurring with numeric literals, and (ii) it would not be used
too often; defaulting is in general undesirable because it
can silently change the semantics.  Again, defaulting is an
example of a compromise in the design of Haskell.  Ideally,
you'd do without it all together, but if you went that way,
you'd end up having to write more type information in your
programs.  And again, I don't suppose there is a universally
satisfactory point on this spectrum.

All the best,
Mark


[EMAIL PROTECTED]  Pacific Software Research Center, Oregon Graduate Institute
Want to do a PhD or PostDoc?   Interested in joining PacSoft?   Let us know!


module SourceFortyTwo where

import Testbed
import HaskellPrims
import HaskellPrelude

-
-- Test Framework:

main :: IO ()
main  = test imports fortyTwo

saveList :: IO ()
saveList  = save "FortyTwo" imports fortyTwo

imports  :: [Assump]
imports   = defnsHaskellPrims ++ defnsHaskellPrelude

-
-- Test Program:

fortyTwo :: [BindGroup]
fortyTwo
 = map toBg
   [[("main", Nothing, [([], ap [evar "print", elit (LitInt 42)])])],
[("main'", Nothing,
 [([], ap [evar "print", 
   eif (ap [econst eqMfun, elit (LitInt 42), elit (LitInt 42)])

mapM/concatMapM

2000-10-18 Thread Sengan Baring-Gould

mapM seems to be a memory hog (and thus also concatMapM). In the following eg:

 main = mapM print ([1..102400] :: [Integer])

memory usage climbs to 1.6M with ghc and needs -K20M, whereas with

 main = print ([1..102400] :: [Integer])

memory usage is only 1300 bytes. 

I instrumented mapM:

 main = mapM2 (_scc_ "p" (\x - print x)) ([1..102400] :: [Integer])

 mapM2 :: Monad m = (a - m b) - [a] - m [b]
 mapM2 f [] = return []
 mapM2 f (c:cs) = _scc_ "a" (=) (_scc_ "d" f c) (\x -
  _scc_ "b" (=) (_scc_ "e" mapM2 f cs) (\xs -
  _scc_ "f" return (x:xs)))

and found that a and b were the worst heap users (according to hp2ps),
ie the two ='s

Why is this so? What can I do about it? My code uses mapM pretty extensively,
and I think its suffering from this problem. I notice that ghc does not seem
to use mapM except in 2 modules.

Another odd thing is that hp2ps says that a  b are the culprits, but the
-p and -px options say p is. Why?

Sengan

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



Re: mapM/concatMapM

2000-10-18 Thread Joe English


[EMAIL PROTECTED] (Sengan Baring-Gould) wrote:

 mapM seems to be a memory hog (and thus also concatMapM).
 In the following eg:
 
  main = mapM print ([1..102400] :: [Integer])
 
 memory usage climbs to 1.6M with ghc and needs -K20M

As a guess: since 'mapM print ([1..102400] :: [Integer])'
has type 'IO [()]', perhaps the result of the IO operation --
a list of 100K empty tuples -- is the culprit, even though
the result is never used.

Does 'mapM_ print ... ' (:: IO ()) perform any better?


--Joe English

  [EMAIL PROTECTED]

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



Re: mapM/concatMapMy

2000-10-18 Thread Sengan Baring-Gould

 
 
 [EMAIL PROTECTED] (Sengan Baring-Gould) wrote:
 
  mapM seems to be a memory hog (and thus also concatMapM).
  In the following eg:
  
   main = mapM print ([1..102400] :: [Integer])
  
  memory usage climbs to 1.6M with ghc and needs -K20M
 
 As a guess: since 'mapM print ([1..102400] :: [Integer])'
 has type 'IO [()]', perhaps the result of the IO operation --
 a list of 100K empty tuples -- is the culprit, even though
 the result is never used.
 
 Does 'mapM_ print ... ' (:: IO ()) perform any better?

Yes, but in the following eg

 main = print $ sum x
 x = _scc_ "x" [1..102400] :: [Integer]

x takes 1M allocations, and I would think that () would be smaller than
an Integer. Therefore I'm not sure that is the reason. The sum is there to
force the evaluation.

Sengan

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



Re: mapM/concatMapMy

2000-10-18 Thread Sengan Baring-Gould

  [EMAIL PROTECTED] (Sengan Baring-Gould) wrote:
  
   mapM seems to be a memory hog (and thus also concatMapM).
   In the following eg:
   
main = mapM print ([1..102400] :: [Integer])
   
   memory usage climbs to 1.6M with ghc and needs -K20M
  
  As a guess: since 'mapM print ([1..102400] :: [Integer])'
  has type 'IO [()]', perhaps the result of the IO operation --
  a list of 100K empty tuples -- is the culprit, even though
  the result is never used.
  
  Does 'mapM_ print ... ' (:: IO ()) perform any better?
 
 Yes, but in the following eg
 
  main = print $ sum x
  x = _scc_ "x" [1..102400] :: [Integer]
 
 x takes 1M allocations, and I would think that () would be smaller than
 an Integer. Therefore I'm not sure that is the reason. The sum is there to
 force the evaluation.

Assuming you are right, why do I see the same 1.6M profile with:

 main = mapM2 (_scc_ "p" (\x - print x)) ([1..102400] :: [Integer])  return ()

 mapM2 :: Monad m = (a - m b) - [a] - m [b]
 mapM2 f [] = return []
 mapM2 f (c:cs) = _scc_ "a" (=) (_scc_ "d" f c) (\x -
  _scc_ "b" (=) (_scc_ "e" mapM2 f cs) (\xs -
  _scc_ "f" return (x:xs)))

Is = not lazy?

Sengan

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