RE: Interrupts in GHC

1999-10-04 Thread Simon Marlow

George Russell writes:
 I can't get Posix.installHandler to do what I expect it to 
 do.  Attached is a sample program.
 If my reading of the documentation is correct, this should 
 prompt with "0" for a reply
 repeatedly until the user interrupts, after which it replaces 
 the current continuation with
 the supplied handler, thus printing out "Interrupted!", and 
 continuing to prompt with "1".
 And so on.  Following is a sample trace (Sparc/Solaris as 
 always).  Note (1) just before
 ^C an extra input line seems to get inserted.  (2) Somehow 
 the supplied handler doesn't
 keep going, instead we return to the old continuation, for no 
 reason I can see.
 What is going on?

I'm not sure which documentation you're reading, but it looks out of date.
The signal-handling semantics in 4.04 are (quoting from the User's Guide, in
the Posix library section):

"if handler is Catch action, a handler is installed which
 will invoke action in a new thread when (or shortly after)
 the signal is received"

So the handler is given a new thread all to itself, and the main thread
carries on running as normal.  If you want the old semantics, you can
arrange to raise an exception in the main thread, or something similar.

Cheers,
Simon



RE: Interrupts in GHC

1999-10-04 Thread Simon Marlow

[ replying to private mail, but cc'ing to the list ]

George Russell asks if he can write a function that traps ^C, with type:

allowInterrupts :: IO a - IO a - IO a

You can implement this as follows: the signal handler needs to send an
exception to the original thread to tell it the signal was caught, and the
original thread then runs the user handler.

Unfortunately... this doesn't work in 4.04 due to a couple of bugs/missing
features: signals don't interrupt threads blocked on I/O, and raising
exceptions in threads blocked on I/O also doesn't work.  Patches for both of
these are attached.  After applying the patches, this code works for me:

main = allowInterrupts 
(getLine  putStr "Ok.") 
 -- or (threadDelay 500  putStr "Ok.")
(putStr "Interrupted.")

handler :: ThreadId - IO ()
handler parent = raiseInThread parent (ErrorCall "interrupted")

allowInterrupts :: IO a - IO a - IO a
allowInterrupts action on_interrupt 
  = do tso - myThreadId 
 (do
  old - installHandler sigINT (Catch (handler tso)) Nothing
  res - action
  installHandler sigINT old Nothing
  return res
  ) `catchAllIO`
( \ e - case e of
ErrorCall "interrupted" - on_interrupt
_other  - throw e)

Cheers,
Simon


begin 600 patch
M*BHJ(%-C:5D=6QE+F,@(#$Y.3DO,#DO,3`@,3$Z,3$Z-3$@("`@(#$N,C4*
M+2TM(%-C:5D=6QE+F,@(#$Y.3DO,3`O,#0@,38Z,#4Z-#8**BHJ*BHJ*BHJ
M*BHJ*BHJ"BHJ*B`W,S(L-S0R("HJ*BH*("`@("`@("!B87)F*")U;F)L;V-K
M5AR96%D("A"3$%#2TA/3$4I.B!44T\@;F]T(9O=6YD(BD["B`@("`@('T*
M("`*("`@(-AV4@0FQO8VME9$]N4F5A9#H*("`@(-AV4@0FQO8VME9$]N
M5W)I=4Z"B$@("!C87-E($)L;V-K961/;D1E;%Y.@HA("`@("`O*B!4;T1O
M("HO"B$@("`@()AF8H(G5N8FQO8VM4:')E860@W)E860L=W)I=4L95L
M87E](BD["B`@"B`@("!D969A=6QT.@H@("`@("!B87)F*")U;F)L;V-K5AR
M96%D(BD["BTM+2`W,S(L-S4T("TM+2T*("`@("`@("!B87)F*")U;F)L;V-K
M5AR96%D("A"3$%#2TA/3$4I.B!44T\@;F]T(9O=6YD(BD["B`@("`@('T*
M("`**R`@(-AV4@0FQO8VME9$]N15L87DZ"B`@("!C87-E($)L;V-K961/
M;E)E860Z"B`@("!C87-E($)L;V-K961/;E=R:71E.@HA("`@("!["B$@("`@
M("`@;%S="`]("9B;]C:V5D7W%U975E7VAD.PHA("`@("`@(9OB`H="`]
M()L;V-K961?75E=65?:0[('0@(3T@14Y$7U133U]1545513L@"B$@("`@
M("`@("`@;%S="`]("9T+3YL:6YK+"!T(#T@="T^;EN:RD@PHA("`@("`@
M(EF("AT(#T]('1S;RD@PHA("`@("`@("`@*FQAW0@/2!TV\M/FQI;FL[
M"B$@("`@("`@("!I9B`H8FQO8VME9%]Q=65U95]T;"`]/2!T*2!["B$@("`@
M("`@("`@()L;V-K961?75E=65?=P@/2!TV\M/FQI;FL["B$@("`@("`@
M("!]"B$@("`@("`@("!G;W1O(1O;F4["B$@("`@("`@?0HA("`@("`@('T*
M(2`@("`@("!B87)F*")U;F)L;V-K5AR96%D("A)+T\I.B!44T\@;F]T(9O
M=6YD(BD["B$@("`@('T*("`*("`@(1E9F%U;'0Z"B`@("`@()AF8H(G5N
M8FQO8VM4:')E860B*3L**BHJ(%-E;5C="YC("`@(#$Y.3DO,#DO,3,@,#@Z
M,C@Z-#4@("`@(#$N,@HM+2T@4V5L96-T+F,@("`@,3DY.2\Q,"\P-"`Q-CHP
M-3HT-@HJ*BHJ*BHJ*BHJ*BHJ*BH**BHJ(#$U+#(P("HJ*BH*+2TM(#$U+#(Q
M("TM+2T*("`C:6YC;'5D92`B4G1S571I;',N:"(*("`C:6YC;'5D92`B4G1S
M1FQA9W,N:"(*("`C:6YC;'5D92`B271I;65R+F@B"BL@(VEN8VQU94@(E-I
M9VYA;',N:"(*("`*("`C(EF(1E9FEN960H2$%615]365-?5%E015-?2"D*
M("`C("!I;F-L=61E(#QS7,O='EP97,N:#X**BHJ*BHJ*BHJ*BHJ*BHJ"BHJ
M*B`Q,3,L,3$X("HJ*BH*+2TM(#$Q-"PQ,C@@+2TM+0H@("`@("`@("\J(9F
M;'5S:"AS=1O=70I.R`J+PH@("`@("`@(9PFEN=8HW1D97)R+"`B87=A
M:71%=F5N=#H@V5L96-T(9A:6QE9%QN(BD["B`@("`@("`@W1G7V5X:70H
M15A)5%]04E,55)%*3L**R`@("`@("!]"BL@("`@("`@+RH@5V4@9V]T($@
MVEG;F%L.R!C;W5L9"!B92!O;F4@;V8@;W5RRX@($EF('-O+"!W92!N965D
M"BL@("`@("`@("H@=\@W1AG0@=7`@=AE('-I9VYA;"!H86YD;5R('-T
MF%I9VAT(%W87DL(]T:5R=VES90HK("`@("`@("`J('=E(-O=6QD()L
M;V-K(9OB!A(QO;F@=EM92!B969OF4@=AE('-I9VYA;"!IPHK("`@
M("`@("`J('-EG9I8V5D+@HK("`@("`@("`J+PHK("`@("`@(EF("AS:6=N
M86QS7W!E;F1I;FH*2D@PHK("`@("`@('-T87)T7W-I9VYA;%]H86YD;5R
J[EMAIL PROTECTED]("`@("`@(')E='5R;CL*("`@("`@("!]"B`@("`@('T*("`*
`
end



Re: Staying alive

1999-10-04 Thread Sven Panne

"Manuel M. T. Chakravarty" wrote:
 I wouldn't call autoconf a hack :-)

OK, MEGA-hack.   :-)   But it's m4 which is the real culprit...

 [...] Anyway, such a class seems to be a nice way for expressing
 the information about marshalable data types.

The class is actually more about "micro"-marshaling, e.g. there are no
methods which actually do some form of memory management. In my current
OpenGL-binding I actually use the following larger class definition:

-
class Eq a = Marshalable a where
   sizeOf:: a - Int
   zeroElem  :: a

   indexOffAddr  :: Addr - Int -a
   readOffAddr   :: Addr - Int - IO a
   writeOffAddr  :: Addr - Int - a - IO ()

   marshal   ::  a  - IO Addr
   marshalList   :: [a] - IO Addr
   marshalListZero   :: [a] - IO Addr

   unmarshal ::Addr - IO  a
   unmarshalList :: Int - Addr - IO [a]
   unmarshalListZero ::Addr - IO [a]

   marshal x = marshalList [x]

   marshalList xs = do
  buf - malloc (length xs * sizeOf (head xs))
  zipWithM_ (writeOffAddr buf) [ 0 .. ] xs
  return buf

   marshalListZero xs = do
  let numElements = length xs
  buf - malloc ((numElements+1) * sizeOf (head xs))
  zipWithM_ (writeOffAddr buf) [ 0 .. ] xs
  writeOffAddr buf numElements (zeroElem `asTypeOf` head xs)
  return buf

   unmarshal buf = liftM head $ unmarshalList 1 buf

   unmarshalList numElements buf =
  mapM (readOffAddr buf) [ 0 .. numElements-1 ]

   unmarshalListZero buf = loop 0 []
  where loop idx accu = do x - readOffAddr buf idx
   if x == zeroElem
  then return $ reverse accu
  else loop (idx+1) (x:accu)
-

This captures usual marshaling/unmarshaling patterns for

   * a single value,
   * a list of values,
   * and a list of values, terminated by a special value (zeroElem).

Two typical instances are:

-
instance Marshalable Char where
   sizeOf   = const @ac_cv_sizeof_char@
   zeroElem = '\0'
   indexOffAddr = indexCharOffAddr
   readOffAddr  = readCharOffAddr
   writeOffAddr = writeCharOffAddr

instance Marshalable Addr where
   sizeOf   = const @ac_cv_sizeof_void_p@
   zeroElem = nullAddr
   indexOffAddr = indexAddrOffAddr
   readOffAddr  = readAddrOffAddr
   writeOffAddr = writeAddrOffAddr
-

The @ac_cv_sizeof_...@ are substituted by the configure script.
Given the above class definition one can write convenient higher order
functions, e.g. for in/inout parameter passing (which actually
involve some kind of alloca):

-
inParamWith :: (a - IO Addr) - (Addr - IO b) - a - IO b
inParamWith marsh act x = do
   buf - marsh x
   ret - act buf
   free buf
   return ret

inParam :: Marshalable a = (Addr - IO b) - a - IO b
inParam = inParamWith marshal

inOutParamWith :: (a - IO Addr) - (Addr - IO a) - (Addr - IO ()) - a - IO a
inOutParamWith marsh unmarsh act x = do
   buf - marsh x
   act buf
   ret - unmarsh buf
   free buf
   return ret

inOutParam :: Marshalable a = (Addr - IO ()) - a - IO a
inOutParam = inOutParamWith marshal unmarshal
-

I know Manuel's code already and the one H/Direct produces. Has
anybody else some FFI-related code and/or suggestions? This could be
a wonderful topic for the wish list, but it would be nice to see the
problems and needs for APIs different from GTK+ and OpenGL first.

Cheers,
   Sven

P.S. for the native speakers: Which spelling is correct, "marshaling"
or "marshalling"? Ispell says "marshaling", but this looks a bit odd
to me.
-- 
Sven PanneTel.: +49/89/2178-2235
LMU, Institut fuer Informatik FAX : +49/89/2178-2211
LFE Programmier- und Modellierungssprachen  Oettingenstr. 67
mailto:[EMAIL PROTECTED]D-80538 Muenchen
http://www.informatik.uni-muenchen.de/~Sven.Panne



Re: To all those who don't like ad-hoc overloading

1999-10-04 Thread Manuel M. T. Chakravarty

Kevin Atkinson [EMAIL PROTECTED] wrote,

 "Manuel M. T. Chakravarty" wrote:
  
  Kevin Atkinson [EMAIL PROTECTED] wrote,
  
   I take it that you are happy with names such as:
  
  [long list of names deleted]
  
   I *hate* languages that try to keep things too simple.  Which is one of
   the reasons I *hate* java.  Please don't make me *hate* Haskell for the
   same reason.
  
  The problem with excessive overloading is that
 
 The key word here is excessive.   If you are confusing your self by
 using the same name for everthing than you need to use seperate function
 names.  So you are saying that haskell should avoid all featurs that can
 be abused. 

Excessive by my definitions if the use of one function name
for `union' and `unionBy'.  What's the harm in using two
function names here?  Where overloading makes sense `union'
uses it already.  If you have to use `unionBy', this is
because the elements of the set are not part of `Eq' or you
want to use something else than standard equality.  In other
words, there is a good reason for using `unionBy' contained
in the algorithm or at least the structure of your program
(otherwise, you have probably already made a mistake in your
class definitions).  As there is such a reason, you should
document it by using `unionBy' instead of `union' -
everything else is, frankly speaking, careless software
engineering.

Haskell encourages good software engineering practice -
that's something I very much like about the language.

  (2) it makes it harder for beginners.
  
  Re (1): Consider the usage of different function names as a
  form of additional documentation.
 
 Yes but many times excessively long function names can make code harder
 to read.

Come on - the two letters difference between `union' and
`unionBy' hardly make a program harder to read.

Manuel






RE: CPP is not part of Haskell

1999-10-04 Thread Simon Peyton-Jones

  Either, cpp (or some preprocessor standard), should be made 
 part of the
  Haskell language definition or Haskell files that require a 
 preprocessor
  should have a different extension. 

GHC dodges this by allowing you to say

{-# OPTIONS -cpp #-}

at the start of your Haskell file Foo.hs.  Any such OPTIONS
are simply added to the command line.  It's a great way to
record *in the source file*, rather than in your Makefile,
what non-standard things your module does.  I often put
-fglasgow-exts, or -syslib misc, in such an OPTIONS line.

I think this is a lot better than using filename suffixes.
I mention it here because it's a facility that may not be
widely known.  I don't know whether other implementations support it.
Of course, even if they do the meaning of the command line 
args may vary between compilers!

 programming language.  IMHO all uses of cpp in Haskell have
 either to do with other non-standard-conformance (eg, using
 unboxed values in GHC, but wanting to use Hugs also) or are
 plainly unnecessary, 

I'm not sure I agree with this.  Keith Wansbrough has an interesting
paper that identifies the ways in which a macro processor can
do thing that ordinary functions can't.   One solution is to add
macros (presumably in a more hygienic form than cpp), but I'm reluctant
to advocate that, because macros undoubtedly do overlap with functions.

So I'm waiting and hoping that someone will have a Really Good Idea.
(And using cpp meanwhile.)

Simon






Re: To all those who don't like ad-hoc overloading

1999-10-04 Thread Kevin Atkinson

"Manuel M. T. Chakravarty" wrote:
 
 Kevin Atkinson [EMAIL PROTECTED] wrote,
 
  I take it that you are happy with names such as:
 
 [long list of names deleted]
 
  I *hate* languages that try to keep things too simple.  Which is one of
  the reasons I *hate* java.  Please don't make me *hate* Haskell for the
  same reason.
 
 The problem with excessive overloading is that

The key word here is excessive.   If you are confusing your self by
using the same name for everthing than you need to use seperate function
names.  So you are saying that haskell should avoid all featurs that can
be abused. 
 
 (1) it is often cute in small programs, but bites you when
 software gets more complex, and

I have never yet hade this problem with my C++ functions and
overloading.  I only use overloading when it will be clear my the
context what it means.

 (2) it makes it harder for beginners.
 
 Re (1): Consider the usage of different function names as a
 form of additional documentation.

Yes but many times excessively long function names can make code harder
to read.
 
 Re (2): There was some overloading in Haskell 1.4, which was
 taken out in Haskell 98 exactly for this reason (usage of
 list comprehensions for other monads than list and the
 overloading of map and (++)).

That is a shame.

-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/






Re: CPP is not part of Haskell

1999-10-04 Thread George Russell

Simon Peyton-Jones wrote:
 One solution is to add
 macros (presumably in a more hygienic form than cpp), but I'm reluctant
 to advocate that, because macros undoubtedly do overlap with functions.
You don't need macros.  (For speed purposes inline functions are obviously
better.)  All you need are (a) a way of defining a constant value (restricted
to type Integer or Bool say) in one file so that it can be used in another file;
(b) a type of compile-time if statement which will branch on simple arithmetic 
and boolean expressions in constant values and constants, which doesn't typecheck
the branch which isn't taken.  For example, this is what Java provides and
I think it's not too bad.  (In Java the compile-time "if" is indistinguishable
from the normal one; I'd rather for Haskell it was called something different,
like _if.)  I think you could get such a solution to work; it wouldn't
be terribly elegant, but it would be a lot more elegant than the current
combination of Haskell + CPP.






Re: Announce: frantk

1999-10-04 Thread Meurig Sage

Hi
This is probably a PATH problem in windows 95. (NT seems a bit more clever
about this.) I don't have access to a windows 95 box at the moment so I
can't test this. As a quick test try running hugs, moving to the
TclHaskellSrc directory and then loading Tcl.hs. If this works then it is
definitely a path problem. Try adding the TclHaskellSrc directory to your
path.

Hope this works, let me know how you get on.

Meurig


 Meurig Sage wrote:
  Announce: FranTk

 I can't get franTk running under Win95. It fails with:
 Error while importing DLL "c:\t\TclHaskellSrc\TclPrim.dll"
 This file does exist. I also tried putting a copy of the dll on the
 windows PATH, in C:\windows.

 I'm using the May99 version of hugs98, and tcl/tk 8.2.

 Any help would be appreciated.

 Also, one note on getting it running under SunOS 5.6: making TclPrim.so
 required uppercasing tclPrim.c



 John Atwood









Re: To all those who don't like ad-hoc overloading

1999-10-04 Thread Jan de Wit

On Sat, 2 Oct 1999, Matt Harden wrote:

[snip]
   
   I like that, but I wish we had a way to get the "head" and "tail" of
   tuples, just as we do with lists, and combine them.  Maybe a (:,)
   operator that works like this:
   
   a :, (b :, ()) = (a,b)
   a :, () = UniTuple a
   a :, (b,c) = (a,b,c)
   a :, (UniTuple b) = (a,b)
   
   Also allow pattern matching on this operator.
   
[snip]
   
   This seems a little too obvious to me.  Has it been suggested and shot
   down before?
   
   Matt Harden
   
Well, you can define a class Splittable:

class Splittable a b c where
  spl :: a - (b,c)  -- split tuple
  lps :: (b,c) - a  -- reverse split

With fairly obvious instances for Splittable a a (), Splittable (a,b) a b,
Splittable (a,b,c) a (b,c) etc. The only problem with this kind of solution
is that when you type, e.g. spl (3,4,5), hoping to obtain (3,(4,5)), hugs
complains with:
ERROR: Unresolved overloading
*** Type   : (Num a, Num b, Num c, Splittable (c,b,a) d e) = (d,e)
*** Expression : spl (3,4,5)

However, it seems that Mark Jones has an extension to Hugs in the works
where you can specify that the types b and c in the class depend on a,
which would resolve this issue. See http://www.cse.ogi.edu/~mpj/fds.html
for details - I really hope the September release comes quickly !!!

Bye,

Jan de Wit
   








Where is Server Side Scripting code?

1999-10-04 Thread Jan Skibinski


Erik Meijer, in his paper "Server Side Scripting in Haskell", FFP, Jan 98
(www.cs.uu.nl/~erik/) claims that his Haskell/CGI library is a part of the
standard Hugs distribution. He also thanks the teams from Yale and
Nottingham for including it as one of the demos in the standard
distribution (of Hugs). I could not find it there though, nor on
Erik's site.

What is available from haskell.org are two much outdated versions of CGI
library: one by Erik himself and one modified (and adopted to Haskell 98)
by Sven Panne. By outdated I mean that they both are based on Erik's
earlier work and much predate the refined and simplified concepts,
quite nicely described in the paper.

So where is the code in question? Is it still available to public
and if yes - who is a keeper?

Jan

  








Re: CPP is not part of Haskell

1999-10-04 Thread George Russell

"Manuel M. T. Chakravarty" wrote:
 
 George Russell [EMAIL PROTECTED] wrote,
 This sounds interesting.  So you want the branch that is not
 taken to be syntactically correct, but it need not type
 check.  How about other semantic constraints (visibility of
 names etc)?  If you want to use this mechanism for selecting
 whether or not to use non-standard features, you probably
 also have to allow that the branch not taken is
 syntactically illegal (eg, use of GHC's unboxed values in
 one branch and plain Haskell in the other).  How is this
 exactly in Java?
I suspect that in Java both branches would have to be syntactically
correct, though I can't be bothered to look it up.  Hmm, I hadn't 
thought of that.  But it shouldn't be hard to think up some way
round which is prettier than the CPP version; it could hardly be
uglier!

If we are going to have a different name for "if" when it is
used in this way (and I think we should anyway) we may as well
call it #if and be like C.  This will mean that existing programs
should go through without much modification. So I suggest
(1) The compiler keeps track of which values at top level are
"constant expressions".  A constant expression is an
Integer, Bool or String, or something obtained thereof
by the obvious operations (arithmetic, comparison,
perhaps if itself, ++).  When a value bound to a constant
expression is exported, its constant expression status
is exported too.  
(2) the CPP conditional syntax (#if, #else, and so on)
but NOTHING ELSE from CPP.  The argument to #if must
be a constant expression.
(3) Where appropriate the compiler may allow values to be
bound to constant expressions on the command line.
Yes I know it's pretty ghastly, but it's still 1 times better
than using CPP.   And I don't think it should be too ghastly to
implement.   The main bother would that the change would have to
be agreed precisely between the Hugs and GHC folk.






Re: To all those who don't like ad-hoc overloading

1999-10-04 Thread Adrian Hey

 On Sun 03 Oct, Manuel M. T. Chakravarty wrote: 
 The problem with excessive overloading is that
 
 (1) it is often cute in small programs, but bites you when
 software gets more complex, and
 (2) it makes it harder for beginners.

I can think of 2 more potential problems with overloading (ad-hoc or otherwise)

(3) It makes it hard to use Haskell as a target language for other
software tools, synthesizers etc unless they adopt essentially the
same type system as Haskell. It would be much easier, I think, if
the 'operational meaning' of a bit of Haskell code is unambiguous
without type checking. By this I mean you could turn type checking
off and still be able to compile the program.

(4) If you have 2 different methods to achieve the same thing (e.g.
2 different algorithms which are the most efficient in different
circumstances, or 2 criteria for comparing values of the same type).
Here you can't use type to select the appropriate method. Instead
you have to make values of the 'same type' look different just so
the correct method can be chosen, which complicates matters a lot.
Giving different names to different functions seems much easier to me.

Regards
-- 
Adrian Hey







RE: ++ vs comprehension

1999-10-04 Thread S.D.Mechveliani

No. I ask this irrelatively to  concat.  I which way comprehensions
might in principle, optimize the prigram with `++' ?






Re: CPP is not part of Haskell

1999-10-04 Thread Manuel M. T. Chakravarty

George Russell [EMAIL PROTECTED] wrote,

 Simon Peyton-Jones wrote:
  One solution is to add
  macros (presumably in a more hygienic form than cpp), but I'm reluctant
  to advocate that, because macros undoubtedly do overlap with functions.

 You don't need macros.  (For speed purposes inline functions are obviously
 better.)  All you need are (a) a way of defining a
 constant value (restricted to type Integer or Bool say) in
 one file so that it can be used in another file;
 (b) a type of compile-time if statement which will branch
 on simple arithmetic and boolean expressions in constant
 values and constants, which doesn't typecheck the branch
 which isn't taken.  For example, this is what Java
 provides and I think it's not too bad.  (In Java the
 compile-time "if" is indistinguishable from the normal
 one; I'd rather for Haskell it was called something
 different, like _if.)  I think you could get such a
 solution to work; it wouldn't be terribly elegant, but it
 would be a lot more elegant than the current combination
 of Haskell + CPP.

This sounds interesting.  So you want the branch that is not
taken to be syntactically correct, but it need not type
check.  How about other semantic constraints (visibility of
names etc)?  If you want to use this mechanism for selecting
whether or not to use non-standard features, you probably
also have to allow that the branch not taken is
syntactically illegal (eg, use of GHC's unboxed values in
one branch and plain Haskell in the other).  How is this
exactly in Java?

Manuel






Re: To all those who don't like ad-hoc overloading

1999-10-04 Thread Kevin Atkinson

On Mon, 4 Oct 1999, Manuel M. T. Chakravarty wrote:

 Kevin Atkinson [EMAIL PROTECTED] wrote,
 
  The key word here is excessive.   If you are confusing your self by
  using the same name for everthing than you need to use seperate function
  names.  So you are saying that haskell should avoid all featurs that can
  be abused. 
 
 Excessive by my definitions if the use of one function name
 for `union' and `unionBy'.  What's the harm in using two
 function names here?  Where overloading makes sense `union'
 uses it already.  If you have to use `unionBy', this is
 because the elements of the set are not part of `Eq' or you
 want to use something else than standard equality.  In other
 words, there is a good reason for using `unionBy' contained
 in the algorithm or at least the structure of your program
 (otherwise, you have probably already made a mistake in your
 class definitions).  As there is such a reason, you should
 document it by using `unionBy' instead of `union' -
 everything else is, frankly speaking, careless software
 engineering.


I am not going to argue with you any more.  We have a different
definitions of what is easy to read.  To me:

  union fun list1 list2

makes perfect sense to me.  To you it may not.  The union and unionBy
is not so much what I object to as having to write two definitions for
union when I should only really have to write one using a generic
comparison function.

Also I hate not being able to have emulations such as

  data Bool = True | False
  data Bool2 = True | False | DontCare

which true adhoc overloading will allow.

Also, sense Haskell does not support objects in the form 
  object-function parms
you have to use
  function object parms

Unfortunately this means that two different objects can not have the same
"method" name unless that method is a type class.  And type classes won't
always work.

Also I hate long complicated system calls with lots of parameters which
you have to explicitly specify in the order given.  True adhoc
overloading will allow me to write an open function such as.

open HANDLE filename ReadOnly
open HANDLE filename Append
open HANDLE filename Write (Overwrite := False)

true adhoc overloading will allow me to do this.

---
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/







Re: Where is Server Side Scripting code?

1999-10-04 Thread Alex Ferguson


Jan Skibinski:
 What is available from haskell.org are two much outdated versions of CGI
 library: one by Erik himself and one modified (and adopted to Haskell 98)
 by Sven Panne. By outdated I mean that they both are based on Erik's
 earlier work and much predate the refined and simplified concepts,
 quite nicely described in the paper.

I encountered this same situation several months ago;  I asked around,
but I'm no further forward, I'm afraid.

Cheers,
Alex.






RE: CPP is not part of Haskell

1999-10-04 Thread Frank A. Christoph

  I'm not sure I agree with this.  Keith Wansbrough has an interesting
  paper that identifies the ways in which a macro processor can
  do thing that ordinary functions can't.   
 
 Is this paper available somewhere?

Keith Wansbrough (1999). Macros and Preprocessing in Haskell. Unpublished. 

directly: http://www.cl.cam.ac.uk/users/kw217/research/misc/hspp-hw99.ps.gz
indirectly: http://www.cl.cam.ac.uk/users/kw217/research/papers.html

--FAC







Re: To all those who don't like ad-hoc overloading

1999-10-04 Thread Mariano Suarez Alvarez

On Mon, 4 Oct 1999, Kevin Atkinson wrote:

 On Mon, 4 Oct 1999, Joe English wrote:
 
  I don't quite see what algorithm you're using
  to decide how many arguments are passed
  to the function.
 
 Neither do I.  I meant to express a general idea.  Perhaps that is not the
 best way to do it but that is what I would like to be able to do.
 
  What would you get if you typed:
  
  foo = foldr union []
 
 since foldr expects the function to have the signature
 (a-b-b) it will use the union which matches it, which
 will be the union :: [a] - [a] - [a] and not
 union :: ( a - a - Bool) - [a] - [a] - [a].

The problem is the two might match! Consider the definitions

union :: [a] - [a] - [a]
unionBy :: (a - a - a) - [a] - [a] - [a]
union = error ""
unionBy = error ""

f = union . map fst

g = unionBy . map fst

(I have dropped the (Eq a) context in the signature for union for
simplicity.) This goes thru the typechecker, and hugs tells me that

f :: [(a,b)] - [a] - [a]
g :: (a - (a - a, b)) - [a] - [a] - [a]


If one were allowed to write union for both union and unionBy, so which
one should one choose?

-- m

---
Mariano Suarez Alvarez
Departamento de Matematica - Universidad Nacional de Rosario
Pellegrini 250 - Rosario 2000 - Argentina 

El autor no responde de las molestias que puedan ocasionar sus escritos:
Aunque le pese
El lector tendra que darse siempre por satisfecho.

Nicanor Parra, `Poemas y antipoemas' (Advertencia al lector)

---







Re: To all those who don't like ad-hoc overloading

1999-10-04 Thread Kevin Atkinson

On Mon, 4 Oct 1999, Joe English wrote:

 Kevin Atkinson wrote:
 
  "Generic comparison function" is not really what I mean here.  What I
  mean is a single generic union which will have its
  comparison function default to (==) if one is not specified.
 
  It COULD be written something like
 
  union (cmp = (==)) l1 l2
...
  where
union l1 l2
  means
union (==) l1 l2
 
 I don't quite see what algorithm you're using
 to decide how many arguments are passed
 to the function.

Neither do I.  I meant to express a general idea.  Perhaps that is not the
best way to do it but that is what I would like to be able to do.

 What would you get if you typed:
 
 foo = foldr union []

since foldr expects the function to have the signature
(a-b-b) it will use the union which matches it, which
will be the union :: [a] - [a] - [a] and not
union :: ( a - a - Bool) - [a] - [a] - [a].

---
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/







Re: CPP is not part of Haskell

1999-10-04 Thread Lennart Augustsson

George Russell wrote:

 Simon Peyton-Jones wrote:
  One solution is to add
  macros (presumably in a more hygienic form than cpp), but I'm reluctant
  to advocate that, because macros undoubtedly do overlap with functions.
 You don't need macros.  (For speed purposes inline functions are obviously
 better.)

I guess you have not been in contact with the Real World (tm).  :-)
If you have a program that needs to compile in say, Haskell 1.3 and Haskell 98,
then you need some kind of preprocessor.  Try changing the syntax of e.g. the
export list with a boolean function.
It's a nasty business, and I'm not advocating the use of preprocessors, but
sometimes it's needed.

--

-- Lennart









Re: Tuples (was: To all those who don't like ad-hoc overloading)

1999-10-04 Thread matth

Jan de Wit wrote:
 
 On Sat, 2 Oct 1999, Matt Harden wrote:
 
 [snip]
   
I like that, but I wish we had a way to get the "head" and "tail" of
tuples, just as we do with lists, and combine them.  Maybe a (:,)
operator that works like this:
   
a :, (b :, ()) = (a,b)
a :, () = UniTuple a
a :, (b,c) = (a,b,c)
a :, (UniTuple b) = (a,b)
   
Also allow pattern matching on this operator.
   
 [snip]
   
This seems a little too obvious to me.  Has it been suggested and shot
down before?
   
Matt Harden
   
 Well, you can define a class Splittable:
 
 class Splittable a b c where
   spl :: a - (b,c)  -- split tuple
   lps :: (b,c) - a  -- reverse split
 
 With fairly obvious instances for Splittable a a (), Splittable (a,b) a b,
 Splittable (a,b,c) a (b,c) etc. The only problem with this kind of solution
 is that when you type, e.g. spl (3,4,5), hoping to obtain (3,(4,5)), hugs
 complains with:
 ERROR: Unresolved overloading
 *** Type   : (Num a, Num b, Num c, Splittable (c,b,a) d e) = (d,e)
 *** Expression : spl (3,4,5)
 

Yes, I have been thinking of almost the same thing, except I would not
have any arbitrary (x) be a 1-tuple (unituple? monotuple?), because then
what is ((x,y))?  A 1-tuple, or a 2-tuple?  Also, under your scheme,

   spl (x,(y,z)) = spl (x,y,z) = (x,(y,z))

... which for some reason bothers me a lot.  That's why I use a UniTuple
datatype above.  Btw, the user would almost never actually *encounter* a
UniTuple.  Certainly zip', show, read, etc. can be defined without using
it.

Another option would be a class that converts tuples to/from a
"cascading pair":

   cascade   (a,b,c) = (a,(b,(c,(
   cascade   ()  = ()
   cascade   (a,b)   = (a,(b,()))
   uncascade (b,())  = UniTuple b  -- or this can be undefined

The un/cascade scheme allows us to avoid 1-tuples altogether.  Of course
un/cascade and spl/lps can be defined in terms of one another.

Btw. I still would want the compiler/interpreter to auto-generate these
class instances for all tuples the way it currently does for Eq, Ord,
Show, Read, Ix, etc...  The nice thing is, instances of those classes
can be created in terms of Splittable (or it's equivalent).  Same goes
for Zippable, of course, and I can think of more uses.

 However, it seems that Mark Jones has an extension to Hugs in the works
 where you can specify that the types b and c in the class depend on a,
 which would resolve this issue. See http://www.cse.ogi.edu/~mpj/fds.html
 for details - I really hope the September release comes quickly !!!

I'll look at the extension.  It seems to be sorely needed.  Without it,
I can't figure out a way to define Zippable (or Eq, Ord, etc.) in terms
of Splittable.  Can you?

 Bye,
 
 Jan de Wit
 

Thanks
Matt






Re: To all those who don't like ad-hoc overloading

1999-10-04 Thread Joe English


Kevin Atkinson wrote:

 "Generic comparison function" is not really what I mean here.  What I
 mean is a single generic union which will have its
 comparison function default to (==) if one is not specified.

 It COULD be written something like

 union (cmp = (==)) l1 l2
   ...
 where
   union l1 l2
 means
   union (==) l1 l2


I don't quite see what algorithm you're using
to decide how many arguments are passed
to the function.

What would you get if you typed:

foo = foldr union []

for example?


--Joe English

  [EMAIL PROTECTED]






Re: To all those who don't like ad-hoc overloading

1999-10-04 Thread Carlos Camarao de Figueiredo


Considering: 

foldr:: (a - b - b) - b - [a] - b
union:: [a] - [a] - [a]   and
union :: ( a - a - Bool) - [a] - [a] - [a]

Then:
f = union . map fst

where:

map:: (a - b) - [a] - [b]
(.):: (a - b) - (c - a) - c - b
fst :: (a,b) - a

has type (in System CT)

---
{ union:: b - [a] - c }. [(b, d)] - [a] - c
---

which comes from the generalisation of the two possibilities: 

 [(a, d)] - [a] - [a]
and
 [(a - a - Bool), d] - [a] - [a] - [a]

Here: 
 b is the generalisation of [a] and (a - a - Bool)
 c is the generalisation of [a] and [a] - [a]

By the way, I would appreciate if someone could explain the type

   g :: (a - (a - a,b)) - [a] - [a] - [a]
*
   (where g = unionBy . map fst)

given by Hugs (ghc behaves differently... ).

Yours,

Carlos