Re: [Haskell-cafe] Guards (Was: Some random newbie questions)

2005-01-07 Thread Jon Cast
Henning Thielemann <[EMAIL PROTECTED]> wrote:


> What about dropping Guards? :-) Are they necessary? Do they lead to
> more readable source code?

Absolutely.  In Haskell's syntax, if-then-else-if interacts badly with
do notation, and Haskell lacks a direct analogy to Lisp's cond.

case () of
  () | p1 -> e1
 | p2 -> e2
 ...

works beautifully as a replacement.  Also, GHC's pattern guards are a
nice feature, and frequently seem clearer than case.  Compare, e.g.,

 parseCmd ln
   | Left err <- parse cmd "Commands" ln
 = BadCmd $ unwords $ lines $ show err
   | Right x <- parse cmd "Commands" ln
 = x

with the Haskell-98 alternative

 parseCmd ln = case parse cmd "Commands" ln of
   Left err -> BadCmd $ unwords $ lines $ show err
   Right x  -> x

The trade-off: using pattern guards makes it harder to verify (and
ensure) that the exact same expression is being matched against; using
case makes it harder to see exactly what is being matched against.

Furthermore, guards are an extension of pattern matching, which means
you can write code like this:

 xn !! n | n < 0  = error "Prelude.(!!): Negative index"
 [] !! n  = error "Prelude.(!!): Index overflow"
 (x:xn) !! n | n == 0 = x
 (x:xn) !! n  = xn !! (n - 1)

Exactly one equation for each edge in the control-flow graph, which is
nice and not easily done (I'm not sure it's even possible) without
guards.

Pattern guards are also nice for implementing ‘views’:

 -- | Convert an 'XMLData' into an equivalent application of
 -- 'Balanced', if possible.  In any case, return an equivalent data
 -- structure.
 balance (Balanced es) = Balanced es
 balance (LeftLeaning (LeftBalanced e:es))
   | Balanced es' <- balance (LeftLeaning es)
   = Balanced (e:es')
 balance (LeftLeaning []) = Balanced []
 balance (RightLeaning [("", "", es)]) = Balanced es
 balance (RightLeaning []) = Balanced []
 balance e = e

Where XMLData can store a (nearly) arbitrary fragment of an XML
document.  The problem being solved by the pattern guard in the second
equation is that the data type is ambiguous; there is more than one way
to represent a ‘balanced’ XML fragment (that is, the concatenation of a
sequence of well-formed XML fragments and CDATA sections).  This
function attempts to coerce the data structure passed in into a
canonical representation; it succeeds if the data is in fact balanced
and fails otherwise.  The pattern guard illustrates how to use this
function as a replacement for pattern matching on Balanced, to catch all
cases where the argument is in fact balanced (we can't use it in this
case as a replacement for the first equation, since that create an
infinite loop, but in other functions we could).

I'm sure there are uses I'm forgetting, but I think that's enough.

> Do they lead to more efficient code? I could perfectly live without
> them up to now.

Well, I could never do without them.

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


[Haskell-cafe] Re: Unicode: Hugs vs GHC (again) was: Re: Some random newbie questions

2005-01-07 Thread Ashley Yakeley
In article 
<[EMAIL PROTECTED]
ft.com>,
 "Simon Marlow" <[EMAIL PROTECTED]> wrote:

> True.  Anyone care to take Hugs' implementation of the character class
> functions and put it in GHC?

There's extensive character property tables in code in
.

The Makefile fetches the tables from the Unicode web-site and generates 
Haskell from that, so they should all be correct. It's Unicode 3.2, so 
it's a bit out of date (current is 4.0.1), but it shouldn't be too hard 
to update.

-- 
Ashley Yakeley, Seattle WA

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


Preventing space leaks without seq (was: Re: [Haskell-cafe] Some random newbie questions)

2005-01-07 Thread Henk-Jan van Tuyl
L.S.,
Olaf <[EMAIL PROTECTED]> wrote:
I'm constantly surprised hearing from so many people about their space
problems. I cannot remember having space problems with my programs. I
don't know what everybody else is doing wrong  I do disagree with
people recommending strictness annotations (seq etc). In contrast, I make
my programs as lazy as possible.
Can you give some rules and/or examples how you do this?
Henk-Jan van Tuyl
--
Using Opera's revolutionary e-mail client:  
https://secure.bmtmicro.com/opera/buy-opera.html?AID=789433
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Implementing computations with timeout

2005-01-07 Thread Tomasz Zielonka
On Fri, Jan 07, 2005 at 11:00:27PM +0100, Tomasz Zielonka wrote:
> Hmmm, TMVar's seem to be significantly (ie. 6 times) faster than MVars
> in some simple tests :)
> 
> Is it expected?

If it is, we can reimplement MVars using STM, when STM becomes stable :)

Best regards,
Tomasz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Implementing computations with timeout

2005-01-07 Thread Tomasz Zielonka
On Fri, Jan 07, 2005 at 04:47:12PM +0100, Tomasz Zielonka wrote:
> On Fri, Jan 07, 2005 at 04:55:05PM +0200, Einar Karttunen wrote:
> > if we use IO as the signature then using the TMVar has few advantages over
> > using an MVar.
> 
> Yes, I think you are right here.

Hmmm, TMVar's seem to be significantly (ie. 6 times) faster than MVars
in some simple tests :)

Is it expected?

Best regards,
Tomasz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Implementing computations with timeout

2005-01-07 Thread Sebastian Sylvan
On Fri, 7 Jan 2005 20:56:42 +0100, Sebastian Sylvan
<[EMAIL PROTECTED]> wrote:
> On Fri, 07 Jan 2005 15:31:10 +0200, Einar Karttunen
>  wrote:
> > Hello
> >
> > What is the best way of doing an computation with a timeout?
> 
> I like the approach taken in  "Tackling the ackward squad":
> 

I should also state that this isn't safe when it comes to asynchronous
exceptions.
If one were to raise an exception in a timeout'd computation it would
simply abort the takeMVar which means the two child processes won't
get killed.

/S

-- 
Sebastian Sylvan
+46(0)736-818655
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Implementing computations with timeout

2005-01-07 Thread Sebastian Sylvan
On Fri, 07 Jan 2005 15:31:10 +0200, Einar Karttunen
 wrote:
> Hello
> 
> What is the best way of doing an computation with a timeout?

I like the approach taken in  "Tackling the ackward squad":

First a funcion which will "race" two IO computations against each
other, returning the "winning" result.
This is accomplished by simply spawning a thread for each computation
which does nothing but evalute the IO computation and putting the
result in an MVar.
Then the MVar is read (this will lock until there is something in the
MVar to read), when finally there is something to read it will
obviously contain the result of the IO computation that completed
first. Then both of the spawned threads are killed (one of them is
already dead at this point) via throwTo.

parIO :: IO a -> IO a -> IO a
parIO a1 a2
 = do m <- newEmptyMVar ;
c1 <- forkIO (child m a1) ;
c2 <- forkIO (child m a2) ;
r <- takeMVar m ;
throwTo c1 Kill ;
throwTo c2 Kill ;
return r
 where child m a = do r <- a
putMVar m r 

Next we simply race the IO computation to be "timed out" against a
thread which delays and then returns Nothing.

timeout :: Int -> IO a -> IO (Maybe a)
timeout n a = parIO a1 a2
where a1 = do r <-a
  return (Just r)
  a2 = do threadDelay n
  return Nothing


/S

-- 
Sebastian Sylvan
+46(0)736-818655
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] The Implementation of Functional Programming Languages

2005-01-07 Thread Simon Peyton-Jones
I'm happy to announce that my out-of-print 1987 book,

The Implementation of Functional Programming Languages

is now available online at


http://research.microsoft.com/%7Esimonpj/papers/slpj-book-1987/index.htm

Very many thanks to Marnie Montgomery, who did all the work.

Happy reading

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


Re: [Haskell-cafe] Hugs vs GHC (again) was: Re: Some randomnewbiequestions

2005-01-07 Thread Lennart Augustsson
Malcolm Wallace wrote:
Lennart writes:
What encoding(s) did hbc allow in source files?  The docs only mention
unicode characters inside character & string literals.
The Java encoding, i.e., \u.

Well, in that case, nhc98 also supports Unicode in source files,
identically to hbc.
Well, you have to support it all the way through, and generate
suitable mangled identifiers in the output, but I presume you do.
-- Lennart
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Hugs vs GHC (again) was: Re: Some randomnewbiequestions

2005-01-07 Thread Malcolm Wallace
"Simon Marlow" <[EMAIL PROTECTED]> writes:
> >>  - Can the Char type hold the full range of Unicode characters?
> >>This has been true in GHC for some time, and is now true in Hugs.
> >>I don't think it's true in nhc98 (please correct me if I'm wrong).
> > 
> > You're wrong :-).  nhc98 has always had 32-bit characters internally.
> 
> I checked the nhc98 sources, and it seems that maxBound::Char is '\255'.

Yes, but nothing prevents you from creating a larger character by e.g.
(toEnum 0x12345678) :: Char

Lennart writes:
> > What encoding(s) did hbc allow in source files?  The docs only mention
> > unicode characters inside character & string literals.
>
> The Java encoding, i.e., \u.

Well, in that case, nhc98 also supports Unicode in source files,
identically to hbc.

Regards,
Malcolm
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Implementing computations with timeout

2005-01-07 Thread Peter Simons
Einar Karttunen writes:

 > What is the best way of doing an computation with a timeout?

At  you'll find a very readable and
straightforward implementation of a generic timeout
function:

  type Timeout = Int
  timeout :: Timeout -> IO a -> IO (Maybe a)

The function uses the "two threads" approach you've
outlined, and it has proven to work nicely in practice.

Peter

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


Re: [Haskell-cafe] Implementing computations with timeout

2005-01-07 Thread Tomasz Zielonka
On Fri, Jan 07, 2005 at 04:55:05PM +0200, Einar Karttunen wrote:
> if we use IO as the signature then using the TMVar has few advantages over
> using an MVar.

Yes, I think you are right here.

Best regards,
Tomasz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Guards (Was: Some random newbie questions)

2005-01-07 Thread Christian Maeder
Henning Thielemann wrote:
What about dropping Guards? :-) Are they necessary? Do they lead to more
readable source code? Do they lead to more efficient code? I could
perfectly live without them up to now.
I hardly need guards too, but their advantage is that they let pattern 
matching fail, resulting in trying out following patterns.

case l of
  [i] | i /= 0 -> (/i)
  _ -> error "a single message here for all other cases"
Cheers Christian
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Implementing computations with timeout

2005-01-07 Thread Tomasz Zielonka
On Fri, Jan 07, 2005 at 04:55:05PM +0200, Einar Karttunen wrote:
> 
> Isn't this buggy if fun just keeps working without throwing an exception
> or using retry? I meant wholly inside STM

There is not that much that you can do inside STM. This may be a problem
if you want to wait for a genuine IO action.

Best regards,
Tomasz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Some random newbie questions

2005-01-07 Thread Ross Paterson
On Fri, Jan 07, 2005 at 08:49:32AM -0500, Paul Hudak wrote:
> I taught our FP class this fall using Hugs, but in the end wish that I 
> had used GHC.  There are lots of little reasons for this, but a big one 
> was a problem with unpredictable space utilization.  I don't have the 
> examples at my fingertips, but there were simple variations of the same 
> program that, by all common-sense reasoning, should have behaved in the 
> opposite way with respect to space than what they exhibited.

Concrete examples would be interesting, especially if they didn't involve
the graphic library.

> Indeed, 
> the problem that you report in your "Sierpinkski Carpet" may likely be a 
> problem with Hugs, and not the graphics lib, and Jacob Nelson's message 
> seems to bear this out.

No: it runs under GHCi, but it uses 16MB.  Hugs has a 2MB heap by default
(the size is measured in 8-byte cells).
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Implementing computations with timeout

2005-01-07 Thread Tomasz Zielonka
On Fri, Jan 07, 2005 at 02:57:19PM +0100, Tomasz Zielonka wrote:
> My guess is it would be something like this, however you may want to do it
> differently to get better compositionality (withTimeout returns an IO action,
> not a STM action):

Maybe this will suffice, but I don't know if the delay thread will be
garbage collected.

  import Control.Concurrent
  import Control.Concurrent.STM
  import Monad (when)

  makeDelay :: Int -> IO (STM ())
  makeDelay time = do
  v <- atomically (newTVar False)
  forkIO $ do
  threadDelay time
  atomically (writeTVar v True)
  return $ readTVar v >>= \b -> when (not b) retry

  withTimeout :: Int -> STM a -> IO (Maybe a)
  withTimeout time fun = do
  delay <- makeDelay time
  atomically (fmap Just fun `orElse` (delay >> return Nothing))

Best regards,
Tomasz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Implementing computations with timeout

2005-01-07 Thread Einar Karttunen
Tomasz Zielonka <[EMAIL PROTECTED]> writes:
>   import Control.Concurrent (forkIO, threadDelay)
>   import Control.Concurrent.STM
>
>   withTimeout :: Int -> STM a -> IO (Maybe a)
>   withTimeout time fun = do
>   mv <- atomically newEmptyTMVar
>   tid <- forkIO $ do
>   threadDelay time
>   atomically (putTMVar mv ())
>   x <- atomically (fmap Just fun `orElse` (takeTMVar mv >> return 
> Nothing))
>   killThread tid
>   return x

Isn't this buggy if fun just keeps working without throwing an exception
or using retry? I meant wholly inside STM - if we use IO as the
signature then using the TMVar has few advantages over using an MVar.

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


Re: [Haskell-cafe] Implementing computations with timeout

2005-01-07 Thread Tomasz Zielonka
On Fri, Jan 07, 2005 at 03:31:10PM +0200, Einar Karttunen wrote:
> Hello
> 
> What is the best way of doing an computation with a timeout?
> 
> A naive implementation using two threads is easy to create - but 
> what is the preferred solution?
> 
> withTimeout :: forall a. Int -> IO a -> IO (Maybe a)

> btw How would I do the same with the new STM abstraction?

My guess is it would be something like this, however you may want to do it
differently to get better compositionality (withTimeout returns an IO action,
not a STM action):

  import Control.Concurrent (forkIO, threadDelay)
  import Control.Concurrent.STM

  withTimeout :: Int -> STM a -> IO (Maybe a)
  withTimeout time fun = do
  mv <- atomically newEmptyTMVar
  tid <- forkIO $ do
  threadDelay time
  atomically (putTMVar mv ())
  x <- atomically (fmap Just fun `orElse` (takeTMVar mv >> return Nothing))
  killThread tid
  return x

PS. STM is cool! :)

Best regards,
Tomasz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Unicode: Hugs vs GHC (again) was: Re: Some random newbie questions

2005-01-07 Thread Simon Marlow
On 07 January 2005 13:01, Dimitry Golubovsky wrote:

> Lennart Augustsson wrote:
>> Simon Marlow wrote:
>> 
>>> Here's a summary of the state of Unicode support in GHC and other
>>> compilers.  There are several aspects:
>>> 
>>>  - Can the Char type hold the full range of Unicode characters?
>>>This has been true in GHC for some time, and is now true in Hugs.
>>>I don't think it's true in nhc98 (please correct me if I'm
>>> wrong). 
> 
> I remember, it was in GHC. But any attempt to output Unicode
> characters using standard I/O functions always ended up outputting
> only low 8 bits. Has anything changed since then?

No, that's still the case (I mentioned it in a separate point in that
message).
 
>>>  - Do the character class functions (isUpper, isAlpha etc.) work
>>>correctly on the full range of Unicode characters?  This is true
>>>in Hugs.  It's true with GHC on some systems (basically we were
>>>lazy and used the underlying C library's support here, which is
>>> patchy). 
> 
> Which basically means that one with older or underconfigured system
> where they do not have permissions/technical possibilities to
> configure locales in the C library properly is out of luck...

True.  Anyone care to take Hugs' implementation of the character class
functions and put it in GHC?

> The reason I asked this question was: I am trying to understand, where
> is internationalization of Haskell compilers on their developers' list
> of priorities, and also how high is demand from users to have at least
> basic internationalization.

We're keen to have it.  The more people that complain about the lack of
it, the faster it'll get done, probably :-)

Cheers,
Simon
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Hugs vs GHC (again) was: Re: Some randomnewbiequestions

2005-01-07 Thread Lennart Augustsson
Simon Marlow wrote:
Many years ago, hbc claimed to be the only compiler with support for
this. 

What encoding(s) did hbc allow in source files?  The docs only mention
unicode characters inside character & string literals.
The Java encoding, i.e., \u.
-- Lennart
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Some random newbie questions

2005-01-07 Thread Paul Hudak
Benjamin Pierce wrote:
OK, I'm taking the plunge and using Haskell in a course I'm teaching this
semester.  To get ready, I've been doing quite a bit of Haskell programming
myself, and this has raised a few questions...
* What are the relative advantages of Hugs and GHC, beyond the obvious (Hugs
  is smaller and easier for people not named Simon to modify, while GHC is a
  real compiler and has the most up-to-date hacks to the type checker)?  Do
  people generally use one or the other for everything, or are they similar
  enough to use Hugs at some moments and GHC at others?
I taught our FP class this fall using Hugs, but in the end wish that I 
had used GHC.  There are lots of little reasons for this, but a big one 
was a problem with unpredictable space utilization.  I don't have the 
examples at my fingertips, but there were simple variations of the same 
program that, by all common-sense reasoning, should have behaved in the 
opposite way with respect to space than what they exhibited.  Indeed, 
the problem that you report in your "Sierpinkski Carpet" may likely be a 
problem with Hugs, and not the graphics lib, and Jacob Nelson's message 
seems to bear this out.

SOEGraphics, by the way, is built on top of HGL, a general graphics lib 
written by Alastair Reid.  At the time, it was the best option that we 
had, but Alastair no longer has time to maintain it, although I believe 
that Ross Paterson may be maintaining it now.  In any case, SOEGraphics 
has grown a big buggy with respect to portability across platforms and 
compilers.  I am about to update the SOE webpage with our current best 
shot at a portable and bug-free version of this, but ultimately I'd like 
to port everything over to something like wxHaskell.

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


RE: [Haskell-cafe] Hugs vs GHC (again) was: Re: Some randomnewbiequestions

2005-01-07 Thread Simon Marlow
On 07 January 2005 12:30, Malcolm Wallace wrote:

> "Simon Marlow" <[EMAIL PROTECTED]> writes:
> 
>> Here's a summary of the state of Unicode support in GHC and other
>> compilers.  There are several aspects:
>> 
>>  - Can the Char type hold the full range of Unicode characters?
>>This has been true in GHC for some time, and is now true in Hugs.
>>I don't think it's true in nhc98 (please correct me if I'm wrong).
> 
> You're wrong :-).  nhc98 has always had 32-bit characters internally.

I checked the nhc98 sources, and it seems that maxBound::Char is '\255'.

>>  - Can you use (some encoding of) Unicode for your Haskell source
>>files? I don't think this is true in any Haskell compiler right
>> now. 
> 
> Many years ago, hbc claimed to be the only compiler with support for
> this. 

What encoding(s) did hbc allow in source files?  The docs only mention
unicode characters inside character & string literals.

Cheers,
Simon
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Implementing computations with timeout

2005-01-07 Thread Einar Karttunen
Hello

What is the best way of doing an computation with a timeout?

A naive implementation using two threads is easy to create - but 
what is the preferred solution?

withTimeout :: forall a. Int -> IO a -> IO (Maybe a)
withTimeout time fun =
  do mv <- newEmptyMVar
 tid <- forkIO (fun  >>= tryPutMVar mv . Just >> return ())
 forkIO (threadDelay time >>  killThread tid >> tryPutMVar mv Nothing >> 
return ())
 takeMVar mv 


btw How would I do the same with the new STM abstraction?

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


Re: [Haskell-cafe] Unicode: Hugs vs GHC (again) was: Re: Some random newbie questions

2005-01-07 Thread Dimitry Golubovsky
Hi,
Lennart Augustsson wrote:
Simon Marlow wrote:
Here's a summary of the state of Unicode support in GHC and other
compilers.  There are several aspects:
 - Can the Char type hold the full range of Unicode characters?
   This has been true in GHC for some time, and is now true in Hugs.
   I don't think it's true in nhc98 (please correct me if I'm wrong).
I remember, it was in GHC. But any attempt to output Unicode characters 
using standard I/O functions always ended up outputting only low 8 bits. 
Has anything changed since then?

 - Do the character class functions (isUpper, isAlpha etc.) work
   correctly on the full range of Unicode characters?  This is true in
   Hugs.  It's true with GHC on some systems (basically we were lazy
   and used the underlying C library's support here, which is patchy).
Which basically means that one with older or underconfigured system 
where they do not have permissions/technical possibilities to configure 
locales in the C library properly is out of luck...

 - Can you use (some encoding of) Unicode for your Haskell source files?
   I don't think this is true in any Haskell compiler right now.
Well, Hugs from CVS accepts source code in UTF-8 (I am not sure about 
locale-based conversion) - at least on my computer. Another thing, 
string literals may be in UTF-8 encoding, but Hugs would not accept 
function/type identifiers in Unicode (i. e. one could not name a type or 
a function in Russian for instance - their names muct be ASCII).

I put an example of such a file in UTF-8 on my web-server:
http://www.golubovsky.org/software/hugs-patch/testutf.hs
Well, even if hbc is mostly dead I must point out that it has supported
this since Unicode was first added to Haskell.  As well as the point
above, of course.
If the GHC implementors feel lazy they can always borrow the Unicode
(plane 0) description table from HBC.  It is a 64k file.
Or in Hugs, there is a shell script (awk indeed, just wrapped in a shell 
script) which parses the Unicode data file and produces a C file (also 
about 64k), and compact set of primitive functions independent from C 
library - src/unix/mkunitable and part of src/char.c in the Hugs source 
tree respectively.

The reason I asked this question was: I am trying to understand, where 
is internationalization of Haskell compilers on their developers' list 
of priorities, and also how high is demand from users to have at least 
basic internationalization.

Dimitry Golubovsky
Middletown, CT

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


Re: [Haskell-cafe] Hugs vs GHC (again) was: Re: Some random newbiequestions

2005-01-07 Thread Malcolm Wallace
"Simon Marlow" <[EMAIL PROTECTED]> writes:

> Here's a summary of the state of Unicode support in GHC and other
> compilers.  There are several aspects:
> 
>  - Can the Char type hold the full range of Unicode characters?
>This has been true in GHC for some time, and is now true in Hugs.
>I don't think it's true in nhc98 (please correct me if I'm wrong).

You're wrong :-).  nhc98 has always had 32-bit characters internally.

>  - Do the character class functions (isUpper, isAlpha etc.) work
>correctly on the full range of Unicode characters?  This is true in
>Hugs.  It's true with GHC on some systems (basically we were lazy
>and used the underlying C library's support here, which is patchy).

In nhc98, currently the character class functions work only on the
8-bit Latin-1 range.

>  - Can you use (some encoding of) Unicode for your Haskell source files?
>I don't think this is true in any Haskell compiler right now.

Many years ago, hbc claimed to be the only compiler with support for this.

>  - Can you do String I/O in some encoding of Unicode?  No Haskell
>compiler has support for this yet, and there are design decisions
>to be made.  Some progress has been made on an experimental prototype
>(see recent discussion on this list).

Apparently some Haskell/XML toolkits already do I/O conversions in a
selection of the encodings permitted by the XML standard, namely ASCII,
Latin-1, UTF-8, and UTF-16 (either byte ordering), but not yet UCS-4
(four possible byte orderings), or EBCDIC.  See for example:
  
http://www.ninebynine.org/Software/HaskellUtils/HaXml-1.12/src/Text/XML/HaXml/Unicode.hs

>  - What about Unicode FilePaths?  This was discussed a few months ago
>on the haskell(-cafe) list, no support yet in any compiler.

Indeed, AFAIK.

Regards,
Malcolm
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Hugs vs GHC (again) was: Re: Some random newbiequestions

2005-01-07 Thread Lennart Augustsson
Simon Marlow wrote:
Here's a summary of the state of Unicode support in GHC and other
compilers.  There are several aspects:
 - Can the Char type hold the full range of Unicode characters?
   This has been true in GHC for some time, and is now true in Hugs.
   I don't think it's true in nhc98 (please correct me if I'm wrong).
 - Do the character class functions (isUpper, isAlpha etc.) work
   correctly on the full range of Unicode characters?  This is true in
   Hugs.  It's true with GHC on some systems (basically we were lazy
   and used the underlying C library's support here, which is patchy).
 - Can you use (some encoding of) Unicode for your Haskell source files?
   I don't think this is true in any Haskell compiler right now.
Well, even if hbc is mostly dead I must point out that it has supported
this since Unicode was first added to Haskell.  As well as the point
above, of course.
If the GHC implementors feel lazy they can always borrow the Unicode
(plane 0) description table from HBC.  It is a 64k file.
-- Lennart
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Some random newbie questions

2005-01-07 Thread Ketil Malde
[EMAIL PROTECTED] writes:

> I'm constantly surprised hearing from so many people about their space
> problems. I cannot remember having space problems with my programs. I
> don't know what everybody else is doing wrong :-) 

At least two common cases.

Extracting compact data structures from large files.  The contents of
the large file is read as a linked list (ugh) of pointers (double ugh)
to 32-bit Chars (triple ugh) -- twelve times the size of the file, if
my calculations are correct.  The contents can't be GC'ed before the
extracted data is fully evaluated.  (Now if the file was an mmap'ed
array, it wouldn't be so bad, perhaps in the next generation IO that
people are discussing this will be easier?)

Naive use of foldl.  I tend to think the default foldl should be
strict (ie. replaced by foldl') -- are there important cases where it
needs to be lazy?

> I do disagree with people recommending strictness annotations (seq
> etc). In contrast, I make my programs as lazy as possible.

...but no lazier :-)

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants

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


RE: [Haskell-cafe] Hugs vs GHC (again) was: Re: Some random newbiequestions

2005-01-07 Thread Simon Marlow
Here's a summary of the state of Unicode support in GHC and other
compilers.  There are several aspects:

 - Can the Char type hold the full range of Unicode characters?
   This has been true in GHC for some time, and is now true in Hugs.
   I don't think it's true in nhc98 (please correct me if I'm wrong).

 - Do the character class functions (isUpper, isAlpha etc.) work
   correctly on the full range of Unicode characters?  This is true in
   Hugs.  It's true with GHC on some systems (basically we were lazy
   and used the underlying C library's support here, which is patchy).

 - Can you use (some encoding of) Unicode for your Haskell source files?
   I don't think this is true in any Haskell compiler right now.

 - Can you do String I/O in some encoding of Unicode?  No Haskell
   compiler has support for this yet, and there are design decisions
   to be made.  Some progress has been made on an experimental prototype
   (see recent discussion on this list).
 
 - What about Unicode FilePaths?  This was discussed a few months ago
   on the haskell(-cafe) list, no support yet in any compiler.

Cheers,
Simon

On 07 January 2005 00:52, Dimitry Golubovsky wrote:

> Hi,
> 
> Looks like Hugs and GHC are being compared again ;)
> 
> I am just interested to know, what is the current status of Unicode
> support in GHC? Hugs has had it for about a year (or more, in CVS) at
> least at the level of recognizing character categories and simple case
> conversions based on the Unicode database files. Also UTF-8 or
> locale-based I/O encoding conversion to internal Unicode is available.
> Does GHC has similar support?
> 
> Some time ago (about 1.5 years) I tried to play with Unicode I/O in
> GHC, and it looked like it did not have much Unicode support back
> then (at least on I/O level). Has anything progressed in this regard
> since then? 
> 
> Most of this list subscribers seem to be GHC users, so can anybody
> answer? 
> 
> BTW when answering the original post (brief quote below) different
> aspects were mentioned, but not internationalization ones. Is it
> really not that important?
> 
> Dimitry Golubovsky
> Middletown, CT
> 
> Benjamin Pierce wrote:
> 
> 
>> * What are the relative advantages of Hugs and GHC, beyond the
>>   obvious (Hugs is smaller and easier for people not named Simon to
>>   modify, while GHC is a real compiler and has the most up-to-date
>>   hacks to the type checker)?  Do people generally use one or the
>>   other for everything, or are they similar enough to use Hugs at
>> some moments and GHC at others? 
> 
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe

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


Re: [Haskell-cafe] Some random newbie questions

2005-01-07 Thread O . Chitil
> * What are the relative advantages of Hugs and GHC, beyond the obvious
> (Hugs
>   is smaller and easier for people not named Simon to modify, while GHC is
> a
>   real compiler and has the most up-to-date hacks to the type checker)?
> Do
>   people generally use one or the other for everything, or are they
> similar
>   enough to use Hugs at some moments and GHC at others?
>

I just completely redesigned our first year undergraduate Haskell module
and considered moving from Hugs to GHC. Because most students have Windows
at home I don't consider installation a problem for GHC. GHC is the
compiler for serious Haskell development. While this is not needed for
beginners, I believe it demonstrates better to students that Haskell is
not just an academic toy language. The error messages of GHC are generally
better than those of Hugs; unfortunately GHC produces very bad parse
errors and beginners tend to make lots of those (however, Hugs has the
infamous unexpected semicolon error message). Hugs stops after the first
error message, while GHC usually reports many errors. I think that for
beginners the long list produced by GHC is more frustrating and they only
repair one error at a time anyway. Hugs is also quicker in reporting an
error. I also do not like that GHC exposes non-Haskell 98 features: if you
type :t length you get length :: forall a. [a] -> Int. "forall" is not
Haskell 98. So because of such a list of slightly beginner-unfriendly
features I decided to stay with Hugs for this year. I might revise this
next year, especially if GHC improves (I should ask Simon&Simon about
these issues...)

I also like the built-in HOOD of Hugs that makes "observe" polymorphic.
However, I'll probably give up my original plan of using it in lectures to
observe functions and thus get a better intuitive feeling for functions as
mappings from inputs to results.


> >   I've clearly got a lot to learn about space usage in Haskell... can
>   someone give me a hint about what is the problem here and how it might
>   best be corrected?
>

I'm glad to see Ross' explanation that the space problem is caused by the
library, because your code looked fine to me.

I'm constantly surprised hearing from so many people about their space
problems. I cannot remember having space problems with my programs. I
don't know what everybody else is doing wrong :-) I do disagree with
people recommending strictness annotations (seq etc). In contrast, I make
my programs as lazy as possible.

Actually I just remember once adding 'seq' to my pretty printing library
to ensure it had the space complexity I wanted (not that there was a
problem in practice). However, shortly afterwards I realised that I could
rewrite that part in a way that made 'seq' superfluous, was shorter,
nicer, and probably even slightly more efficient.

Ciao,
Olaf

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


[Haskell-cafe] Guards (Was: Some random newbie questions)

2005-01-07 Thread Henning Thielemann

On Fri, 7 Jan 2005, Simon Peyton-Jones wrote:

> | * As far as I can determine, there is no way to check pattern matches
> for
> |   exhaustiveness.  Coming from OCaml, this feels like losing a
> significant
> |   safety net!  How do people program so as not to be getting dynamic
> match
> |   failures all the time?
> 
> GHC has -fwarn-incomplete-patterns and -fwarn-overlapped-patterns.  But
> the code implementing these checks is old and crufty, and the warnings
> are sometimes a bit wrong -- at least when guards and numeric literals
> are involved.  I think they are accurate when you are just using
> "ordinary" pattern matching.
> 
> Cleaning up this bit of GHC is a long-standing to-do item, if anyone
> feels motivated to undertake it.  It's a well-defined task, with plenty
> of well-written papers explaining how to do it -- but it's tricker than
> it seems at first!

What about dropping Guards? :-) Are they necessary? Do they lead to more
readable source code? Do they lead to more efficient code? I could
perfectly live without them up to now.

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


RE: [Haskell-cafe] Some random newbie questions

2005-01-07 Thread Simon Peyton-Jones
| * As far as I can determine, there is no way to check pattern matches
for
|   exhaustiveness.  Coming from OCaml, this feels like losing a
significant
|   safety net!  How do people program so as not to be getting dynamic
match
|   failures all the time?

GHC has -fwarn-incomplete-patterns and -fwarn-overlapped-patterns.  But
the code implementing these checks is old and crufty, and the warnings
are sometimes a bit wrong -- at least when guards and numeric literals
are involved.  I think they are accurate when you are just using
"ordinary" pattern matching.

Cleaning up this bit of GHC is a long-standing to-do item, if anyone
feels motivated to undertake it.  It's a well-defined task, with plenty
of well-written papers explaining how to do it -- but it's tricker than
it seems at first!

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


RE: [Haskell-cafe] The implementation of Functional

2005-01-07 Thread Simon Peyton-Jones
The online-readable copy is all ready to go.  I'm just awaiting a final
"ok" from Marnie and I'll announce it.  For a paper copy we'll await
John's Cafepress efforts.  Much thanks to both Marnie and John.

Simon

| -Original Message-
| From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of
| robert dockins
| Sent: 06 January 2005 19:22
| To: haskell-cafe
| Subject: [Haskell-cafe] The implementation of Functional
| 
| 
| The following discussion occurred last September.  Is there any kind
of
| update on any version of this book?
| 
| -
| 
| John Meacham writes:
|  > > >I am looking for the book "The implementation of Functional
|  > > >Programming languages" by S. L. Peyton Jones.
| 
|  > > This book is out of print and currently there is no electronic
version
|  > > of it. The Haskell bookstore folk are working on reconstructing
it and
|  > > making it available for print-on-demand,
|  > > http://www.cafepress.com/haskell_books/, but it's not clear when
|  > > exactly it will be available.
|  > >
|  > > Your other option is to try to find a used copy, but they are
pretty
|  > > expensive.
|  >
|  > I am working on getting that book available in the haskell
bookstore. I
|  > searched quite a while before I found a used printed copy at a
|  > reasonable price and my search was part of my motivation for
creating
|  > the bookstore.
|  >
|  > It is a bit trickier than the other books on the site because I
only
|  > have a scanned in copy of the print version to work with, rather
than
|  > LaTeX source. but I should have time this week to get it online.
|  > John
| 
| My wife (mainly) and I, with Simon's permission, have been working on
| getting a web-enabled version of this available for quite some time.
It
| hovers on the brink of completion, and should be there Real Soon Now
as
| well.  This will include a web enabled table of contents and next and
back
| buttons.
| 
| If I'd known how much time she would put in, I'd have never asked her
for "a
| small favor"...
| 
| Dave Barton
| EDAptive Computing
| 
| ___
| Haskell-Cafe mailing list
| Haskell-Cafe@haskell.org
| http://www.haskell.org/mailman/listinfo/haskell-cafe
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe