RE: Parsing qualified types

1999-06-09 Thread Simon Marlow

 Consider the following two Modules:
 
 File A.lhs:
 ==
  module A where
 
  data A a = MkA a
 ==
 
 File B.lhs:
 ==
  module B where
 
  import qualified A
 
  type A a = A.A a--- Problem!
 ==
 
 ghc-4.03 (current sources) complains while compiling B.lhs:
 
 B.lhs:5: parse error on input `.'

Fixed, thanks for the report.

Cheers,
Simon



RE: CVS Snapshot Bug?

1999-06-09 Thread Simon Marlow


 CVS Snapshot Bug?
 Please let me know if you need more information.

Fixed today, thanks for the report.

Cheers,
Simon



RE: Help: Segfault | Where is the *.hc for 4.02 ?

1999-06-09 Thread Simon Marlow


 I've tried `ghc-4.02-i386-unknown-linux.tar.gz' in-place, but even
 "hello world" will dump core.
 
 Some info about my box:
 
 glibc-2.1.1

I think the conclusion is that recent glibcs don't work with ghc.
Unfortunately we don't have a box here to test on, so if anyone can help
narrow down the problem and/or mail those responsible we'd be grateful.

 BTW, I've tried to give ghc `-optc-g', but all ghc-4.02 versions which
 I have, include those being compiled by myself, cause `ld' to dump
 core, even with glibc-2.0.7 and gcc 2.7.2.3 :-(

We don't support/reccommend compiling with -optc-g :-)  The reason is that
ghc  post-processes the assembly output from gcc, and the script simply
doesn't understand the debugging info inserted by -g.  Nevertheless, ld
shouldn't dump core.

As per the well-known joke, "Don't do that then!"

Simon



digits of large integer

1999-06-09 Thread S.D.Mechveliani

Anatoli Tubman wrote:

T How can I *efficiently* print (i.e. find the decimal, or in
T general N-ary, representation of) large Integers, like factorial of 1?


Lennart Augustsson [EMAIL PROTECTED]  replied

A Use hbc?  It uses the gmp routine to convert an Integer to a String.
A Converting 1! to a String takes much less time than computing it.


The cost of computing N-ary digit(s) of some  f(n)  
may change in many times, depending on what special method is applied
for the given  f. 
Consider, for example, 8-ary digits for  2^n.  They cost almost nothing.
Probably, the initial question concerns mathematics rather than 
programming, or a programming tool choice.

--
Sergey Mechveliani
[EMAIL PROTECTED]










Re: how to write a simple cat

1999-06-09 Thread Hannah Schroeter

Hello!

On Fri, Jun 04, 1999 at 12:18:31PM +0200, Friedrich Dominicus wrote:

 [...]

  splitFilterMap unSplitFn afterMap filterPredicate beforeMap splitFn =
unSplitFn . map afterMap . filter filterPredicate . map beforeMap . splitFn
 [...]

 sorry this looks morre terrible to me than all solutions before, IMO way
 to much parameters and the names don't give me a good hint of what e.g
 beforeMap does. 

That's a HOF that first splits something up to a list using splitFn
(or with the generalization I mentioned, to a monad), then maps a
function over that list (namely beforeMap, because it's mapped
*before* the filter), filters something out (using the filterPredicate),
then again maps a function (namely afterMap, because it's mapped
*after* the filter), then somehow joins the list (or monad), using
unSplitFn.

  splitFilter unSplitFn filterPred splitFn =
splitFilterMap unSplitFn id filterPred id splitFn

That's just a specialization if there's no need for mapping a function
over the list before or after the filtering.

  lenGt limit list = length list  limit

That's used as filter predicate.

  processFile limit = splitFilter unlines (lenGt limit) lines
  -- for the unnumbered version
OR

 I think s.th in that directin is somewhar what I like more

  numberElems = zip [1..]

  number2str (nr,l) = show nr ++ '\t' : l
 I would not call it number2 s.th it does not expplain to me that
 something is printed so maybe 
 print_number_str_pair or the like would be fine for me

But the function doesn't print either. It converts to a string.
Therefore 2str. You could call it
  numberStrPair2String
more accurately.

  processFile limit = splitFilterMap unlines number2str (lenGt limit . snd)
id (numberElems . lines)

 I don't think that I could work with splitFilterMap. Nevertheless is
 shows me all way lead to ROME ;-)

Hmmm. I think using higher order functions to encapsulate programming
structures (i.e. function concatenations, applications, etc.) is one
thing that makes up functional programming.

Just consider standard combinators like
  map, filter, foldl, foldr, sequence (Monads ahead :-) ), ...

 I re-wrote that stuff in Python and I've to admit it's way easier to
 understand for me (not even talking of writing). But I think it was  a
 good example to learn how FP-trained would do it. It's a long long way
 to go;-)

Did you use the more functional parts of Python there? map? filter? :-)

 Regards
 Friedrich

Regards, Hannah.





y2k compliance

1999-06-09 Thread Hugo Bouckaert

Hi

I would like to know whether haskell compilers (hugs, hbc and lmlc) are
fuly y2k compliant. Can anyone fill me in on this?

Thanks

Hugo

--
Dr Hugo Bouckaert - Systems Administrator, Computer Science UWA
Tel: +(61 8) 9380 2878 / Fax: +(61 8) 9380 1089
Email: [EMAIL PROTECTED] / Web: http://www.cs.uwa.edu.au/~hugo








RE: Language Feature Request: String Evaluation

1999-06-09 Thread Frank A. Christoph

 In principle I can do this, but:
 1. how do I hide the import of show String to replace it w/ my own?
 2. If I do replce show String what else will break?
 3. If instead I define an eshow function that strips "", how do I minimize
 the perforamnce hit of quote stripping?
 4. If I want to share my code, I have to share both the actual codebase as
 well as the preprocessor code.  This seems like sucha  basic language
 syntax issue that I shouldn't have to worry about which version of haskell
 your collaborators are running.  Everyone writing their own preprocessor
 will severely balkanize the language.

Hm, it seems to me that that is the cost of being a maverick.

 5. How does the use of this pre-processor interact w/ tools like Derive
 and PolyP which are also implemented as preprocessors?

 That being said, I would be happy to take a shot at HacWrite if it had a
 shot of becoming part of the language definition (or if it was a standard
 part of the various haskell distributions: ghc, hugs, hbc,etc.) and if
 Magnus would allow it.

 Is there a good lanugage reason to object to this feature?  It seems like
 a no brainer imprpovement.

(Allow me to play devil's advocate.)

Not everyone uses Haskell to do web page processing or text processing, and
Haskell already has too much syntactic sugar. I don't like your notion of
changing the semantics of Show String, and I don't like the implicit show
coercions for variables that get substituted into a string. (Whenever
coercions get to be a pain, my instinct is to hide them in the plumbing of a
set of combinators.) Preprocessing introduces another stage into the
compilation process, and makes it that much more difficult to understand a
program; interaction between preprocessors can be tricky (as you pointed
out).

--FC






Re: how to write a simple cat

1999-06-09 Thread Hannah Schroeter

Hello!

On Wed, Jun 02, 1999 at 01:29:12AM -0700, Simon Peyton-Jones wrote:

 [...]

  - Would people actually add stuff?  I'm a bit skeptical, but it would
be great to have my skepticism proved unfounded.  

I think, Friedrich and those who helped him could have posted their
questions and suggestions and answers to a Wiki-Wiki similarly easily
like to the Haskell mailing list.

Anyway, I think the interested questions of a learning person are
a good motor to provide answers, explanations, and so on that are
comprehensible for a "newbie" (as incomprehensible answers provoke
further questions, that often finally lead to something that's
understood by at least the one asking the questions, except s/he
gave up).

 Simon 

Hannah.





Re: y2k compliance

1999-06-09 Thread Jerzy Karczmarczuk

Hugo Bouckaert wrote:

 I would like to know whether haskell compilers (hugs, hbc and lmlc) are
 fuly y2k compliant. Can anyone fill me in on this?


... and , if you are already here,...
could somebody explain, please, what does it mean to have a compiler
which is *NOT* y2k compliant, what is the difference between "full"
and "not full" compliance, and why should we really care.

(Please, - if I might be a little rigid - don't tell me about false
 dates returned by the OS, etc. I want to know how a language compiler
 may have anything to do with this Nessie...)


Jerzy Karczmarczuk
Caen, France.
June 9th, year -237 before the Really New Functional Era (*)




(*) At that moment our beloved Pope will finally decide that the 
True Doctors might be promoted Saints, and they need not go
to Hell even if their wifes were Episcopal Church priests.





Re: Language Feature Request: String Evaluation

1999-06-09 Thread Magnus Carlsson

S. Alexander Jacobson writes:
  In principle I can do this, but:
  1. how do I hide the import of show String to replace it w/ my own?
  2. If I do replce show String what else will break?

I'd rather let the preprocessor insert calls to eshow, and leave show
as it is.

  3. If instead I define an eshow function that strips "", how do I minimize
  the perforamnce hit of quote stripping?

Maybe you could make eshow a member in a class EShow, which defaults
to show, and make a special instance for Char (add a member eshowList).

  4. If I want to share my code, I have to share both the actual codebase as
  well as the preprocessor code.  This seems like sucha  basic language
  syntax issue that I shouldn't have to worry about which version of haskell
  your collaborators are running.  Everyone writing their own preprocessor
  will severely balkanize the language.

I think it's a good idea to use a preprocessor for experimenting with
your own language extensions. When (and if) the extensions settle and
turn out to be useful, you could consider proposing them as part of a
language definition.

  5. How does the use of this pre-processor interact w/ tools like Derive
  and PolyP which are also implemented as preprocessors?

I don't know. Buth the HacWrite preprocessor is simpleminded, it only
looks for the new text lexemes, and doesn't know about the Haskell
syntax. If you run such a preprocessor first, I think it would work.

  That being said, I would be happy to take a shot at HacWrite if it had a
  shot of becoming part of the language definition (or if it was a standard
  part of the various haskell distributions: ghc, hugs, hbc,etc.) and if
  Magnus would allow it.
  
  Is there a good lanugage reason to object to this feature?  It seems like
  a no brainer imprpovement.

I don't see any need to put something like this into the language
definition for the moment. But if you want to use HacWrite, I could
try to put it on some web page.

/M

  
  -Alex-
  
  
  ___
  S. Alexander JacobsonShop.Com
  1-212-697-0184 voice The Easiest Way To Shop
  
  On Tue, 8 Jun 1999, Lennart Augustsson wrote:
  
   "S. Alexander Jacobson" wrote:
   
HacWrite certainly seems like an improvement over Haskell.
However, it is just not as good as the scripting languages.
HacWrite still requires the author to differentiate between strings and
other types, still requires explicit use of show and still requires more
typing and curly balancing.  Isn't this nicer?
   
"insert into mytable values (NULL,'$var1','$(var2+var3)','$var3')
   
   
   So add your own little modification to HacWrite.  It would be easy enough
   to add $ interpolation.
   
   -- Lennart
   
   





Re: y2k compliance

1999-06-09 Thread Adrian Hey

On Wed 09 Jun, Jerzy Karczmarczuk wrote: 
 ... and , if you are already here,...
 could somebody explain, please, what does it mean to have a compiler
 which is *NOT* y2k compliant,

I have found that some compilers put the date and time of compilation in the
resulting object files, so it is possible that such a complier might suffer
a Y2K problem, even on a Y2K compliant OS.
 
 what is the difference between "full"
 and "not full" compliance,

I don't know, this looks like IT salesman speak to me. Perhaps "not full" 
compliance means it will get dates wrong, but won't do anything worse (like
crash or destroy files).

 and why should we really care.

This can be a real pain if you're working under a QA system that demands that
software builds are repeatable (I.E. they will always generate the byte for
byte identical object files, given the same sources). I suppose this is true
whether or not the the compiler is Y2K compliant, but as a point of principal
I would expect all information generated by a compiler to be correct. You
never know when you might end up using that information (to update libraries
for example).

Regards
-- 
Adrian Hey






RE: y2k compliance

1999-06-09 Thread Mark P Jones

Hi Hugo,

| I would like to know whether haskell compilers (hugs, hbc and lmlc) are
| fuly y2k compliant. Can anyone fill me in on this?

My understanding is that none of the current Haskell implementors
can afford to answer a question like this because none of us have
the developer, support, or legal resources that would be required
to back it up.  It must therefore be left to individuals or groups
of users to determine an appropriate notion of y2k compliance for
their own use, and to take responsibility for determining whether
the appropriate systems meet those standards.  We already provide
source and documentation to help with any such assessment, but we
cannot take it any further.  Of course, if someone does carry out
a y2k  evaluation on one or more Haskell systems, and chooses to
publish their results, then everybody can benefit.

All the best,
Mark






Re: how to write a simple cat

1999-06-09 Thread Friedrich Dominicus

Hannah Schroeter wrote:
 
 Hello!
 
 On Fri, Jun 04, 1999 at 12:29:45PM +0200, Friedrich Dominicus wrote:
  [...]
 
   What is difficult is that by using some predefined function, one can
   express very much in very small code. I believe Haskell is even more
   expressive than most OO languages with comparable libraries
   (perhaps except Smalltalk, as that has also a very compact syntax).
 
  I havn't made my mind if that is positive of negative. Sometimes it
  remind me of Perl and I'm not a big lover from it.
 
 Somehow that's not really fair towards Haskell. Perl is made up
 of many special cases, and in some other places, you have to use
 major hackery to achieve some goal (mind the "OO" part of Perl,
 for just one example).

Now Haskell is on the other hand not quite fair to me. It makes me look
as if I never have seen or programmed. I'm not thinking I'm the king of
hacking, but I'm quite able to write some pieces of code. If using
Haskell I have the feeling to ran against a wall, if I have s.th whih is
trivial in e.g Python I have to fight to find a solution in Haskell.
Maybe that's unfairf but it's quite different from all the things I
know. 

 
   Another difficulty is monadic I/O. Perhaps you should exercise
   programming with standard higher-order functions without I/O
   a bit more, so that you master that difficulty and don't have
   to *simultaneously* understand both the HOF things and I/O.
 
  That might be good advice but I/O is one of the most essential things
  and I have to know how to use it proper for writing small skripts.
 
 I think exercise with the purely functional, non-I/O core (and perhaps
 interact like someone else suggested) teaches you the mode of
 thinking in purely functional languages. That thinking can also
 help you understand the way I/O is implemented in a referentially
 transparent way.

I disagree, small scripts spend most of the time doing I/O if I don't
understand how to do that I'm not able to even write the most simple
things. This is eg. true for my cat ...

Till then
Friedrich





Re: how to write a simple cat

1999-06-09 Thread Hannah Schroeter

Hello!

On Fri, Jun 04, 1999 at 12:29:45PM +0200, Friedrich Dominicus wrote:
 [...]

  What is difficult is that by using some predefined function, one can
  express very much in very small code. I believe Haskell is even more
  expressive than most OO languages with comparable libraries
  (perhaps except Smalltalk, as that has also a very compact syntax).

 I havn't made my mind if that is positive of negative. Sometimes it
 remind me of Perl and I'm not a big lover from it.

Somehow that's not really fair towards Haskell. Perl is made up
of many special cases, and in some other places, you have to use
major hackery to achieve some goal (mind the "OO" part of Perl,
for just one example).

Haskell has a very small, rather regular core syntax, with a bit
of syntactical sugar on top (type classes [translated to
records of "methods"], list comprehensions, monadic do-expressions),
but that syntax allows to define rather high level functions
*in Haskell itself* (see the Hugs prelude for the definitions and
see that very few of those definitions are actually references to
primitives, for example), and usually with very clean definitions
(though the GHC prelude implementation sometimes uses hacks to
get more efficient implementations).

  Another difficulty is monadic I/O. Perhaps you should exercise
  programming with standard higher-order functions without I/O
  a bit more, so that you master that difficulty and don't have
  to *simultaneously* understand both the HOF things and I/O.

 That might be good advice but I/O is one of the most essential things
 and I have to know how to use it proper for writing small skripts.

I think exercise with the purely functional, non-I/O core (and perhaps
interact like someone else suggested) teaches you the mode of
thinking in purely functional languages. That thinking can also
help you understand the way I/O is implemented in a referentially
transparent way.

 [...]

 This comments helped me. So I think I will put them under my pillow;-)

 Regards and thanks
 Friedrich

Regards, Hannah.