Re[2]: give equal rights to types and classes! :)

2006-02-03 Thread Dave Menendez
Bulat Ziganshin writes:

> Now i'm trying to generalize my functions parameters/results to type
> classes instead of single types. for example, getFileSize function can
> return any numeric value, be it Integer, Word or Int64. This,
> naturally, results in those long and awkward signatures. Allowing to
> write type of result as just "Integral" makes signature smaller
> and more understandable for me:
> 
> getFileSize :: Stream Monad h -> Monad Integral

How does that type translate back into current Haskell? Assuming
"Stream" is a type, and not a class, I see at least three possibilities:

(Integral a, Monad m) => Stream m h -> m a
(Integral a, Monad m1, Monad m2) => Stream m1 h -> m2 a
(Integral a, Monad m) => (forall m. Monad m => Stream m h) -> m a
-- 
David Menendez <[EMAIL PROTECTED]> | "In this house, we obey the laws
  |of thermodynamics!"
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: give equal rights to types and classes! :)

2006-02-03 Thread Marcin 'Qrczak' Kowalczyk
Bulat Ziganshin <[EMAIL PROTECTED]> writes:

> if my idea was incorporated in Haskell, this change don't require
> even changing signatures of most functions working with arrays -
> just Array type become Array interface, what a much difference?

What would 'Eq -> Eq -> Ord -> Bool' mean?
'(Eq a, Eq b, Ord c) => a -> b -> c -> Bool'?
  '(Eq a, Ord b) => a -> a -> b -> Bool'?
  '(Eq a, Ord a) => a -> a -> a -> Bool'?

-- 
   __("< Marcin Kowalczyk
   \__/   [EMAIL PROTECTED]
^^ http://qrnik.knm.org.pl/~qrczak/
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: [Haskell-cafe] Re[2]: strict Haskell dialect

2006-02-03 Thread John Meacham
On Fri, Feb 03, 2006 at 07:33:12PM -, Brian Hulley wrote:
> One question is how to get some kind of "do" notation that would work well 
> in a strict setting.
> The existing "do" notation makes use of lazyness in so far as the second 
> arg of  >> is only evaluated when needed. Perhaps a new keyword such as 
> "go" could be used to use >>= instead ie:

you can override (>>) in your monad

instance Monad ... where
a >> b = a `seq` b `seq` (a >>= \_ -> b)


unless I am misunderstanding what you want.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: The dreaded M-R

2006-02-03 Thread Scott Turner
Following the helpful call to attend to priorities, I reluctantly return to 
the M-R discussion. I believe a point has been missed that should be a part 
of this thread.

On 2006 January 30, Josef Svenningsson wrote:
> But the most important argument against M-R hasn't been put forward yet.
>
> Haskell is, and has always been, a non-strict language. *Not* a lazy
> language.

That is correct, but it is not a welcome argument. Haskell's unspecified 
evaluation order is elegant, and gives implementers a happy flexibility. But 
Haskell has no need to allow innovative experiments within the report.

On the contrary, practical Haskell programs and libraries rely on sharing. 
Without sharing, the humble Fibonacci example takes exponential time. If the 
report were to clearly mandate the sharing that nearly everyone counts on, it 
would be a benefit. The := syntax suggested by John Hughes is an obvious 
point at which sharing could be mandated. 

The wiki page 
http://hackage.haskell.org/trac/haskell-prime/wiki/MonomorphismRestriction
counts "introducing a concept of sharing into the report" as a negative. In 
the larger context of bolstering Haskell's support for mainstream 
applications, sharing is worthwhile.
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Dictionary definitions on wiki

2006-02-03 Thread Ross Paterson
On Fri, Feb 03, 2006 at 07:09:40PM +, Philippa Cowderoy wrote:
> I just added a ticket requesting that some definitions be added to the 
> wiki (so that other pages and tickets can link to them, helping to 
> demystify jargon for those who don't specialise in specific fields). I've 
> also included quick definitions for "predicative" and "impredicative" in 
> the ticket, as these were asked for on the mailing list earlier and will 
> no doubt crop up again in type system discussions.

Wouldn't the wiki on haskell.org be the ideal place for this?
The definitions would be useful for much more than Haskell'.

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


objective data on use of extensions

2006-02-03 Thread Isaac Jones
I would like to strive to find objective data on the use of
extensions.  I started a table here which summarizes how popular
extensions are in real-life code.  We need more data points, though.

http://hackage.haskell.org/trac/haskell-prime/wiki/ExtensionsExperiment

I have a short program which queries the hackage database, gets some
details about all of the packages there, and summarizes them into a
table.  Right now, there really aren't that many packages on
HackageDB, but hopefully more will appear.

HackageDB is here:
http://hackage.haskell.org/ModHackage/Hackage.hs?action=home

You can upload packages with Cabal-Put, but it's pretty hackish right
now.  I put detailed installation instructions on the wiki:
http://hackage.haskell.org/trac/hackage/wiki/CabalPut

A list of cabal packages that might be good for uploading is here:
http://hackage.haskell.org/trac/hackage/wiki/CabalPackages

The more packages we get into HackageDB, the more accurate objective
data we can build.  Let me know if you want to help!


peace,

  isaac
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Dictionary definitions on wiki

2006-02-03 Thread Philippa Cowderoy
I just added a ticket requesting that some definitions be added to the 
wiki (so that other pages and tickets can link to them, helping to 
demystify jargon for those who don't specialise in specific fields). I've 
also included quick definitions for "predicative" and "impredicative" in 
the ticket, as these were asked for on the mailing list earlier and will 
no doubt crop up again in type system discussions.

Would anyone like to act on this or contribute more definitions to the 
ticket while it's waiting?

-- 
[EMAIL PROTECTED]

Performance anxiety leads to premature optimisation
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Priorities

2006-02-03 Thread Tomasz Zielonka
On Fri, Feb 03, 2006 at 11:18:58AM -0600, John Goerzen wrote:
> On Fri, Feb 03, 2006 at 05:56:41PM +0100, Tomasz Zielonka wrote:
> > On Fri, Feb 03, 2006 at 10:03:08AM -0600, John Goerzen wrote:
> > > I know, of course, that Java green threads and Haskell forkIO threads
> > > are called "threads", but I personally believe its misleading to call it
> > > concurrency -- they're not doing more than one thing at a time.
> > 
> > Aren't you thinking about Parallellism?
> 
> No.
> 
> > http://en.wikipedia.org/wiki/Concurrency_%28computer_science%29
> > In computer science, concurrency is a property of systems which
> > consist of computations that execute overlapped in time
> 
> You're not doing anything simultaneously ("overlapped in time") when
> you're using poll and select (only).  To do something simultaneously in
> Unix, you'd have to either use fork() or start a thread.

Concurrent computations can be sliced into smaller pieces and
interleaved - so there is no need to perform many things simultaneously.
That's how Unix works on uniprocessors - at every time point the CPU
is executing at most one task. Are you arguing that uniprocessor Unix
doesn't provide concurrency?

There are some differences between Unix and GHC process scheduling (I
think that in some special cases GHC's threads can't be preempted, eg.
in tight loops without allocations), but they are not that big.

The point is that on a uniprocessor everything is performed sequentially
at some level. When we talk about Unix, it's the level of OS
implementation, with GHC it's the level of RTS. Yet in both cases we get
quite a good impression of concurrent execution, and it's rather more
productive to think in terms of concurrency.

Best regards
Tomasz

-- 
I am searching for programmers who are good at least in
(Haskell || ML) && (Linux || FreeBSD || math)
for work in Warsaw, Poland
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Tim Sweeney talks about Haskell

2006-02-03 Thread Robert Dockins
Somewhat apropos.  The following recent post on LtU links to some  
slides by Tim Sweeney (Epic Games) wherein he discusses things he  
does and doesn't like about Haskell.


Notable points:

  == Positive on ST (implies need for rank 2 types)
  == Positive on Concurrency and STM
  == Positive on list comprehension (but would like to see array  
comprehension)

  == Positive on declarative initialization
  == Wants static type guarantees about integer overflow, array bounds
  == Wants a good, safe way to do dynamic casts
  == Not happy with runtime cost of lazy evaluation, suggests  
lenient evaluation

  == Claims "purely functional is the right default"!
  == Doesn't like the syntax
  == Claims there are problems with programming in the large (see  
last slide)



Anyway, some further fuel for the fire.

http://lambda-the-ultimate.org/node/1277


There is a link to PDF of the slides a couple of posts down...



Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG



___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: MPTCs and functional dependencies

2006-02-03 Thread Isaac Jones
Henrik Nilsson <[EMAIL PROTECTED]> writes:

> Dear all,
>
> John Mecham wrote:
>
>> Yeah, I have been coming to the same conclusion myself. it pains me a
>> lot. (monad transformers! I need thee!) but its not like fundeps will
>> go away, they will just still be experimental so it isn't the end of
>> the world.
>
> But isn't the whole point of Haskell' to standardise those features
> that are agreed to be necessary for writing real-world
> applications and libraries in a reasonable way?
>
> My concern is not that I fear not being able to compile my programs
> after Haskell' is done. I'm worried about too much code not being
> Haskell' compliant in the end, and, worse, too many people deciding
> that they still have to rely on extensions beyond Haskell' for writing
> "real" applications and libraries.

I am very concerned about this as well.  In most of my production
code, I avoid extensions, but MPTC and functional dependencies are two
that I have not been able to avoid.  Any time I use the class system,
I use MPTC, anytime I use MPTC, I use fundeps.

The trouble with "blessing" fundeps is that they might not pan out in
the end, and it would be a shame to add them to Haskell' and then
remove them again for Haskell'' (if there were such a thing) in favor
of associated types, for instance.

How do we solve this dilemma?  Some proposals that have come up:

 - Simon has proposed that we examine a limited version of functional
   dependencies.

 - Another option, though a scary one at this point, is to look
   closely at associated types.

 - Another option is to punt; we declare them as an extension and
   figure out a way to "bless" extensions (beyond Cabal, I guess).

 - Any others?

Can someone put together a wiki page these choices with trade-offs?
Ravi, Manuel?

peace,

  isaac
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re[2]: Priorities

2006-02-03 Thread Bulat Ziganshin
Hello Tomasz,

Friday, February 03, 2006, 2:00:23 PM, you wrote:

>> >> Personally, I'm not sure about caseless underscore, concurrency, natural
>> >> numbers and parallel list comprehensions.
>> 
>> TZ> The design of Haskell was so great, that we could add concurrency as
>> TZ> a library without introducing any problems... but we have
>> TZ> concurrency in the standard anyway...
>> 
>> concurrency should go into the Standard Library specification. there
>> is just nothing to say about this in the _language_ standard

TZ> Agreed!

well, there is just one exception - _foreign_ functions should carry
"blockable" specification. that will only emphasize imperfection of
non-Haskell world :)))



-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Unary operators [was: Re: ~ patterns]

2006-02-03 Thread Thomas Davie


On Feb 3, 2006, at 9:34 AM, Bulat Ziganshin wrote:


Hello Benjamin,

Friday, February 03, 2006, 2:29:47 AM, you wrote:

(+ x) --->> (? + x)

i like this idea! but i tink that it's too late for such  
incompatible change :(


really, unary operators can be added to language without any troubles.
we need only to prohibit using of the same symbol for unary and binary
operators:

unary 9 #

#n = n-1

f = #1-1

we can even allow prefix and postfix operators as long as they all  
have

different names


The notable exception in this case, '-' (or anything starting with  
-), which breaks block comment syntax (see my earlier example).


Bob
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: FilePath as ADT

2006-02-03 Thread Aaron Denney
On 2006-02-03, Ross Paterson <[EMAIL PROTECTED]> wrote:
> On Fri, Feb 03, 2006 at 12:24:28PM +, Axel Simon wrote:
>> Yes, and I suppose not being opaque about a file name (i.e. FilePath =
>> [Word8]) is superior.
>
> Maybe.  You might want [Word8] under Unix and [Word16] under Win32.

Right.  I think "Generic File Handling" should not be considered the
base, but layered on top of Unix, Win32 and possibly MacOS, if unix
doesn't cover that.

-- 
Aaron Denney
-><-

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Priorities

2006-02-03 Thread Aaron Denney
On 2006-02-03, John Goerzen <[EMAIL PROTECTED]> wrote:
> On Fri, Feb 03, 2006 at 05:56:41PM +0100, Tomasz Zielonka wrote:
>> On Fri, Feb 03, 2006 at 10:03:08AM -0600, John Goerzen wrote:
>> > I know, of course, that Java green threads and Haskell forkIO threads
>> > are called "threads", but I personally believe its misleading to call it
>> > concurrency -- they're not doing more than one thing at a time.
>> 
>> Aren't you thinking about Parallellism?
>
> No.
>
>> http://en.wikipedia.org/wiki/Concurrency_%28computer_science%29
>> In computer science, concurrency is a property of systems which
>> consist of computations that execute overlapped in time
>
> You're not doing anything simultaneously ("overlapped in time") when
> you're using poll and select (only).  To do something simultaneously in
> Unix, you'd have to either use fork() or start a thread.

That was his point.  Threading is a way of structuring a program.
Parallelism is a strategy for exploiting that structuring (and others).

-- 
Aaron Denney
-><-

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Priorities

2006-02-03 Thread John Goerzen
On Fri, Feb 03, 2006 at 05:56:41PM +0100, Tomasz Zielonka wrote:
> On Fri, Feb 03, 2006 at 10:03:08AM -0600, John Goerzen wrote:
> > I know, of course, that Java green threads and Haskell forkIO threads
> > are called "threads", but I personally believe its misleading to call it
> > concurrency -- they're not doing more than one thing at a time.
> 
> Aren't you thinking about Parallellism?

No.

> http://en.wikipedia.org/wiki/Concurrency_%28computer_science%29
> In computer science, concurrency is a property of systems which
> consist of computations that execute overlapped in time

You're not doing anything simultaneously ("overlapped in time") when
you're using poll and select (only).  To do something simultaneously in
Unix, you'd have to either use fork() or start a thread.

-- John
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Priorities

2006-02-03 Thread John Meacham
On Fri, Feb 03, 2006 at 10:03:08AM -0600, John Goerzen wrote:
> On Fri, Feb 03, 2006 at 01:00:32AM -0800, John Meacham wrote:
> > On Fri, Feb 03, 2006 at 08:40:27AM -, Simon Peyton-Jones wrote:
> > > The interface can be a library, but (a) what libraries are available is
> > > part of the language definition and (b) it's hard to build a good
> > > implementation without runtime support.  And the nature of the runtime
> > > support depends on what the library interface is.
> > 
> > If we had a good standard poll/select interface in System.IO then we
> > actually could implement a lot of concurrency as a library with no
> > (required) run-time overhead. I'd really like to see such a thing get
> 
> Maybe this is just me being dense, but how is poll or select
> concurrency?  There is no multiprocessing involved; it is simply a more
> efficient way to find which file descriptors are ready for some I/O
> action.

Yeah, it doesn't. however I thought I'd bring it up becauese it is
related and is a hole in the current haskell set up. even on
implementations with concurrency such a thing is useful as many tasks
actually are easier to implement by hand this way when you need fine
control over scheduling and whatnot.

It's not so much that it's "a more efficient" way as its the only way
for any serious application. GHCs concurrency is a nice interface to it,
but it is quite high-level  and access to the functionality at a medium
level in a standardized way would be quite beneficial and allow all the
state threaded style programs without necesarisy needing full blown
concurrency. Also, providing hPoll is as simple as any FFI wrapper with
no implemenation consequences othen than additions to the library so it
is quite a bargain indeed for what you get.

> I know, of course, that Java green threads and Haskell forkIO threads
> are called "threads", but I personally believe its misleading to call it
> concurrency -- they're not doing more than one thing at a time.

this whole field is rife with ambiguous terminology. it has already been
a source of confusion several times.

I think 'state-threads' are the accepted term for this sort of thread,
but am unsure.

> > the ability to write thread-safe (but not thread using) libraries
> > portably. which means MVars and foreign annotations but nothing more.
> 
> Yes.  Plus, I'd say, the presence of threading primitives that return
> certain well-defined exceptions or something along those lines, so that
> it's not necessary to know whether multithreading is supported at
> compile time.

It would be odd to have routines in the standard that are only
standardized to fail :). We couldn't include those in the standard
without saying what their correct behavior is when they worked, which is
exactly the task I don't think we can acomplish. Actually, I think it
would be difficult to even specify what those primitives are, let alone
their exact semantics.

Also, I can't think of any reason you would ever want to defer such a
decision to run time. either your program needs concurrency and thus
should fail at compile time if it isn't available or it just needs to be
concurrent-safe in which case it will succeed and work portably because
we have included the primitives needed to allow that.


> Right now, we have forkIO, which seems, to me, like a fancy wrapper
> around select or poll.  It's very nice, really.
> 
> I'm not clear, though, on how to integrate other C libraries that have
> their own async I/O systems into all of this.  (For instance, LDAP or
> SQL libraries)  

this is a well known issue even outside of haskell land. various
solutions have evolved, the glib main loop, liboop, libevent, if ghc
were to switch to one then that would allow some sort of
interoperability but none are perfect, and each is mutually exclusive in
general.

this is another reason I feel a hPoll is important, because its low
level control is often needed for interacting with other libraries in
tricky situations like this.

> The exact interaction between FFI, forkIO, forkOS, etc. is, to me,
> extremely vague right now.  It also seems much more complex than in
> other languages, and perhaps varies from one Haskell implementation to
> the next.

I am positive it varies, even if there were a (somewhat odd) concerted
effort to emulate ghcs behavior, I doubt others would get it right any
time soon. It is just such a tricky field! All languages have issues
here, some are better at hand waving them away though or just ignoring
them.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Priorities

2006-02-03 Thread Tomasz Zielonka
On Fri, Feb 03, 2006 at 10:03:08AM -0600, John Goerzen wrote:
> Maybe this is just me being dense, but how is poll or select
> concurrency?  There is no multiprocessing involved; it is simply a more
> efficient way to find which file descriptors are ready for some I/O
> action.
> 
> I know, of course, that Java green threads and Haskell forkIO threads
> are called "threads", but I personally believe its misleading to call it
> concurrency -- they're not doing more than one thing at a time.

Aren't you thinking about Parallellism?

http://en.wikipedia.org/wiki/Concurrency_%28computer_science%29
In computer science, concurrency is a property of systems which
consist of computations that execute overlapped in time

http://en.wikipedia.org/wiki/Parallel_programming
Parallel computing is the simultaneous execution of the same task (split
up and specially adapted) on multiple processors in order to obtain
results faster.

This agrees with what I have read in many texts on the subjects.

Best regards
Tomasz

-- 
I am searching for programmers who are good at least in
(Haskell || ML) && (Linux || FreeBSD || math)
for work in Warsaw, Poland
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Priorities

2006-02-03 Thread John Goerzen
On Fri, Feb 03, 2006 at 12:00:23PM +0100, Tomasz Zielonka wrote:
> > TZ> The design of Haskell was so great, that we could add concurrency as
> > TZ> a library without introducing any problems... but we have
> > TZ> concurrency in the standard anyway...
> > 
> > concurrency should go into the Standard Library specification. there
> > is just nothing to say about this in the _language_ standard

> Agreed!

We should be careful to not take too narrow a view of the meaning of the
word "language", or at least not in the public output of this group.

Many people would, for instance, consider the standard set of libraries
in Java to be part of the language.  The same could be said for Perl and
Python.

-- John
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Priorities

2006-02-03 Thread John Goerzen
On Fri, Feb 03, 2006 at 01:00:32AM -0800, John Meacham wrote:
> On Fri, Feb 03, 2006 at 08:40:27AM -, Simon Peyton-Jones wrote:
> > The interface can be a library, but (a) what libraries are available is
> > part of the language definition and (b) it's hard to build a good
> > implementation without runtime support.  And the nature of the runtime
> > support depends on what the library interface is.
> 
> If we had a good standard poll/select interface in System.IO then we
> actually could implement a lot of concurrency as a library with no
> (required) run-time overhead. I'd really like to see such a thing get

Maybe this is just me being dense, but how is poll or select
concurrency?  There is no multiprocessing involved; it is simply a more
efficient way to find which file descriptors are ready for some I/O
action.

I know, of course, that Java green threads and Haskell forkIO threads
are called "threads", but I personally believe its misleading to call it
concurrency -- they're not doing more than one thing at a time.

> the ability to write thread-safe (but not thread using) libraries
> portably. which means MVars and foreign annotations but nothing more.

Yes.  Plus, I'd say, the presence of threading primitives that return
certain well-defined exceptions or something along those lines, so that
it's not necessary to know whether multithreading is supported at
compile time.

> A nice, well thought out standardized poll/select/asynchronous IO
> library as part of System.IO. this will fill a much needed gap between
> full concurrency and synchronous IO which is currently a void and will
> provide just enough run-time support for experimenting with portable
> concurrency libraries.

Well, I must admit to being confused at the present state of things.

Right now, we have forkIO, which seems, to me, like a fancy wrapper
around select or poll.  It's very nice, really.

I'm not clear, though, on how to integrate other C libraries that have
their own async I/O systems into all of this.  (For instance, LDAP or
SQL libraries)  

The exact interaction between FFI, forkIO, forkOS, etc. is, to me,
extremely vague right now.  It also seems much more complex than in
other languages, and perhaps varies from one Haskell implementation to
the next.

-- John

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Comment Syntax

2006-02-03 Thread John Meacham
On Fri, Feb 03, 2006 at 01:43:15PM -, Simon Marlow wrote:
> GHC treats the Unicode categories Sm, Sc, Sk and So as symbols, FWIW.
> These are the same characters for which Data.Char.isSymbol returns True.

cool. I will try to make jhc do the same thing.

> How do you implement the Data.Char predicates in jhc, BTW?

for now just via the following ffi call:
(though the plain 'module Char' just uses the report definitions for now)

> newtype CType = CType Int
>
> -- | Get a ctype other than one of the defaults.
>
> ctype :: String -> IO CType
> ctype s = withCString s >>= c_wctype
>
> t_alnum, t_alpha, t_blank, t_cntrl,
>  t_digit, t_graph, t_lower, t_print,
>  t_punct, t_space, t_upper, t_xdigit, t_none :: CType
>
> t_alnum = unsafePerformIO (ctype "alnum")
> t_alpha = unsafePerformIO (ctype "alpha")
> t_blank = unsafePerformIO (ctype "blank")
> t_cntrl = unsafePerformIO (ctype "cntrl")
> t_digit = unsafePerformIO (ctype "digit")
> t_graph = unsafePerformIO (ctype "graph")
> t_lower = unsafePerformIO (ctype "lower")
> t_print = unsafePerformIO (ctype "print")
> t_punct = unsafePerformIO (ctype "punct")
> t_space = unsafePerformIO (ctype "space")
> t_upper = unsafePerformIO (ctype "upper")
> t_xdigit = unsafePerformIO (ctype "xdigit")
> t_none = CType 0
>
> foreign import ccall "wctype.h iswctype" c_iswctype :: Char -> CType -> IO Int
> foreign import ccall "wctype.h wctype" c_wctype :: CString -> IO CType


John


--
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


RE: Unicode, was Comment Syntax

2006-02-03 Thread Simon Marlow
On 03 February 2006 04:07, Taral wrote:

> On 2/2/06, John Meacham <[EMAIL PROTECTED]> wrote:
>> but it currently doesn't recognize any unicode characters as possible
>> operators. which it should, but I am just not sure how to specify
>> that yet until some sort of standard develops. Once there are more
>> unicode compliant compilers out there something will evolve probably.
> 
> Character attributes are defined in unicode:
> 
> http://www.unicode.org/Public/UNIDATA/
> 
> It's just a matter of mapping. Perhaps this is worth considering
> amending for Haskell'? The Haskell98 grammar talks about "symbol",
> "uppercase", "lowercase", while Unicode is a bit more... diverse.

This is already mentioned on the wiki:

http://haskell.galois.com/cgi-bin/haskell-prime/trac.cgi/wiki/UnicodeInH
askellSource

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


RE: Comment Syntax

2006-02-03 Thread Simon Marlow
On 03 February 2006 00:40, John Meacham wrote:

> On Thu, Feb 02, 2006 at 06:19:43PM -0600, Taral wrote:
>> Got a unicode-compliant compiler?
> 
> sure do :)
> 
> but it currently doesn't recognize any unicode characters as possible
> operators. which it should, but I am just not sure how to specify that
> yet until some sort of standard develops. Once there are more unicode
> compliant compilers out there something will evolve probably. Right
> now I am thinking of being able to add a PRAGMA to force some
> characters to be interpreted as operators just so that they can start
> being used now, even though there isn't a standard set you can count
> on yet. 

GHC treats the Unicode categories Sm, Sc, Sk and So as symbols, FWIW.
These are the same characters for which Data.Char.isSymbol returns True.

How do you implement the Data.Char predicates in jhc, BTW?

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


Re: Wanted: unified annotation syntax, was: Re: strict Haskell dialect

2006-02-03 Thread Dinko Tenev
I'll second that.

I'll just throw in that not all pragmas ({-# ... #-}) are really
annotations, because they do not necessarily pertain to one particular
entity each.  Some could be attached -- e.g. DEPRECATED, INLINE /
NOINLINE, SPECIALIZE.  Others, however, couldn't -- say, rewrite rules
-- and are bound to remain as pragmas, even if the rest are converted
to annotations.


Cheers,

DInko


On 2/2/06, Johannes Waldmann <[EMAIL PROTECTED]> wrote:
> John Meacham wrote:
>
> > module $hat.Foo(..) where ...
>
> Before we invent more ad-hoc notation for annotations
> (we already have deriving, {-# .. #-}, {-! .. -!} (DrIFT) )
> can we replace all (or most) of this with a unified annotation syntax,
> e. g. Java uses "@" notation which is basically allowed
> at any declaration, and (important points) programmers can
> define their own annotations, and annotations can also have values.
> Also, they have a retention policy saying whether they should be visible
> at compile time or at run time. Compile time is for tools/preprocessors,
> and visibility at run time is helpful for reflection. see e. g. JLS 9.6f
> http://java.sun.com/docs/books/jls/third_edition/html/interfaces.html#9.6
> some example text is here:
> http://dfa.imn.htwk-leipzig.de/~waldmann/draft/meta-haskell/
>
> Best regards,
> --
> -- Johannes Waldmann -- Tel/Fax (0341) 3076 6479/80 --
>  http://www.imn.htwk-leipzig.de/~waldmann/ ---
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


comment on: Make underscore 'caseless' (Ticket 72)

2006-02-03 Thread Johannes Waldmann
http://hackage.haskell.org/trac/haskell-prime/wiki/Underscore

I think it is basically the wrong idea to encode (type and) usage
information in the name of an identifier. One should use the type system
for that, or, failing that, annotations. Something like

data Foo = Foo | @SuppressWarnings("unused") Bar

See my proposal for unified and extendible annotations
http://www.haskell.org//pipermail/haskell-prime/2006-February/000279.html
http://java.sun.com/docs/books/tutorial/java/javaOO/annotations.html

Of course compilers/IDEs are free to support whatever naming conventions
they want but I think such conventions should not go into the language
standard.

Best regards,
-- 
-- Johannes Waldmann -- Tel/Fax (0341) 3076 6479/80 --
 http://www.imn.htwk-leipzig.de/~waldmann/ ---

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: FilePath as ADT

2006-02-03 Thread Ross Paterson
On Fri, Feb 03, 2006 at 12:24:28PM +, Axel Simon wrote:
> Yes, and I suppose not being opaque about a file name (i.e. FilePath =
> [Word8]) is superior.

Maybe.  You might want [Word8] under Unix and [Word16] under Win32.

> So why is the whole Unicode proposal under "adopt: none"? Did nobody
> look at that yet?

No, there's no formal proposal yet.  It would probably be two or three
proposals (source, I/O, strings).

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: FilePath as ADT

2006-02-03 Thread Axel Simon
On Fri, 2006-02-03 at 12:13 +, Ross Paterson wrote:
> On Fri, Feb 03, 2006 at 12:06:28PM +, Axel Simon wrote:
> > I think this is not yet discussed on the wiki:
> >
> > [FilePath as String or ADT]
> 
> The issue (and the related one with program arguments and environment
> variables) is mentioned under CharAsUnicode.

Yes, and I suppose not being opaque about a file name (i.e. FilePath =
[Word8]) is superior. My fault.

So why is the whole Unicode proposal under "adopt: none"? Did nobody
look at that yet?

Axel.

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: FilePath as ADT

2006-02-03 Thread Ross Paterson
On Fri, Feb 03, 2006 at 12:06:28PM +, Axel Simon wrote:
> I think this is not yet discussed on the wiki:
>
> [FilePath as String or ADT]

The issue (and the related one with program arguments and environment
variables) is mentioned under CharAsUnicode.

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


FilePath as ADT

2006-02-03 Thread Axel Simon
I think this is not yet discussed on the wiki:

>From the recent post to the Haskell list:

 Forwarded Message 
From: Krasimir Angelov <[EMAIL PROTECTED]>
To: haskell 
Subject: [Haskell] System.FilePath survey

[..]
* Will you be happy with a library that represents the file path
as String? The opposite is to use ADT for it. The disadvantage is that
with the current IO library we should convert from ADT to String and
back again each time when we have to do any IO. The ADT may have
advantages for the internal library implementation.
[..]
Cheers,
  Krasimir
___

The chance to change the libraries is a chance to get the FilePath type
right. We had a thorough discussion on this already, I think there was
a silent consensus that the FilePath must be an abstract data type due to
Unicode reasons. The discussion back then evolved around the following:

The task: Remove all files in a directory recursively.

The problem: In case the current encoding is UTF-8, filenames stored in
a different locale can comprise illegal UTF-8 sequences and are
therefore not representable as FilePath which is a Unicode string. Even
if the resulting Unicode sting is not 'error ".."', it is impossible to
call 'delete' on that file name, since fromUTF8 . toUTF8 cannot be the
identity function if the UTF8 byte sequence is illegal.

The solution: FilePath must be an abstract data type that is a sequence
of bytes. Programmers should only convert these to Unicode for
displaying them and otherwise treat them as opaque entities. In case of
invalid UTF-8 strings, the corresponding String will have an "invalid
unicode code character" substituted.

The solution of representing a file name abstractly is also used by the
Java libraries. Are there any objections to changing this?

Axel.



___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Priorities

2006-02-03 Thread Tomasz Zielonka
On Fri, Feb 03, 2006 at 12:43:24PM +0300, Bulat Ziganshin wrote:
> Friday, February 03, 2006, 10:52:22 AM, you wrote:
> 
> >> Personally, I'm not sure about caseless underscore, concurrency, natural
> >> numbers and parallel list comprehensions.
> 
> TZ> The design of Haskell was so great, that we could add concurrency as
> TZ> a library without introducing any problems... but we have
> TZ> concurrency in the standard anyway...
> 
> concurrency should go into the Standard Library specification. there
> is just nothing to say about this in the _language_ standard

Agreed!

Best regards
Tomasz

-- 
I am searching for programmers who are good at least in
(Haskell || ML) && (Linux || FreeBSD || math)
for work in Warsaw, Poland
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


things to throw away?

2006-02-03 Thread Claus Reinke

We must find *something* to throw away though! :-)
Simon


Indeed. One of the things I had been hoping for in Haskell'
was the removal of the many conservative restrictions put
into earlier definitions: they complicate the language definition,
restrict expressiveness, and have prompted various extensions.

- mr
- the whole bunch of "you can't do this (we think)" in type 
   classes and their instances, when nowadays we know that 
   type class instances are all about logical meta-programming 
   at the type level. non-decidability should still be optional, 
   but also, at least standardised.

- ..

(btw, I hope I'm not misquoting, but I think it was Mark Jones
who said that permitting complex type parameters was more 
important than having multiple parameters in type classes - you 
can simulate multiple parameters by tupling)


anyway. Just as I was disturbed by the many not-yet-existing
features under discussion, I am worried about the new trend
of proposing not to include old friends (MPTC, concurrency,
functional dependencies, ..). If that should happen, Haskell'
will be just as irrelevant as Haskell98 was, before the FFI
addendum (how many Haskell98 programs were there that
did not use "primitives"?).

So I repeat my opinion: the committee should not limit itself
to a single, all-encompassing standard. There are things that
can and need to be standardised, for which we do not yet
know whether they should be frozen into _the_ standard
forever, and there are things that need to be standardized,
for which the standardization might take too long to match
the Haskell' timeline.

The established answer to such changeability in software is
to modularize, and the same should happen for the language
standard. I agree with Patryk here (I even like the idea of
abusing imports to specify language extensions in use, though
I would simply use a combination of imports and reserved
parts of the module hierarchy, without modifying the import
syntax at all). 

Perhaps we cannot have Concurrent Haskell in all Haskell' 
implementations, or perhaps Functional Dependencies will 
be replaced by something else in the future. But when I use 
either of them, I want to be able to write code that any 
supporting Haskell'+CH+FD implementation will understand 
and interpret the same way, and about which any 
non-supporting Haskell' implementation will be able to tell
me exactly what it is that it doesn't support (instead of giving 
obscure syntax errors). Scanning over the import lines and

reporting that "no, sorry, we don't have Language.Haskell.
Extensions.Types.FancyRankN here" should do the latter
quite nicely, and allows to document the former in the same
way as libraries.

Cheers,
Claus

PS Someone suggested searching the libraries for features
   that are in use and should therefore be included in Haskell'.
   Another thing to look for are preprocessor directives
   protecting differences between implementations. Also,
   perhaps someone could write a simple program analyzer
   that people could run over their own code repositories
   to report features in use back here (perhaps based on
   the extended Haskell syntax parser)? You'll need something
   like this anyway, as part of moving code from Haskell98 
   and Haskell(GHC), ... to Haskell'.


___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: concurrency (was Re: Priorities)

2006-02-03 Thread Ganesh Sittampalam

On Fri, 3 Feb 2006, Ross Paterson wrote:


As another example, Ben Rudiak-Gould recently pointed out that the
inclusion of stToIO breaks threaded state reasoning for ST, e.g.
readSTRef won't necessarily get what your last writeSTRef wrote (because
the region might be RealWorld, with other threads modifying it).


You can still reason about something of type ST s a, it's just with the 
proviso that the reasoning is only correct when it is (perhaps indirectly) 
invoked by runST.


Cheers,

Ganesh
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re[2]: strict Haskell dialect

2006-02-03 Thread Bulat Ziganshin
Hello Wolfgang,

Friday, February 03, 2006, 1:46:56 AM, you wrote:
>> i had one idea, what is somewhat corresponding to this discussion:
>>
>> make a strict Haskell dialect. implement it by translating all
>> expressions of form "f x" into "f $! x" and then going to the standard
>> (lazy) haskell translator. the same for data fields - add to all field
>> definitions "!" in translation process. then add to this strict
>> Haskell language ability to _explicitly_ specify lazy fields and lazy
>> evaluation, for example using this "~" sign
>>
>> what it will give? ability to use Haskell as powerful strict language,
>> what is especially interesting for "real-world" programmers. i have
>> found myself permanently fighting against the lazyness once i starting to
>> optimize my programs. for the newcomers, it just will reduce learning
>> path - they don't need to know anything about lazyness

WJ> Since laziness often allows you to solve problems so elegantly, I'm really 
WJ> scared of the idea of a "Strict Haskell"! :-(  Is laziness really so 
"unreal" 
WJ> that real-world programmers have to see it as an enemy which they have to 
WJ> fight against?

WJ> In fact, I was kind of shocked as I read in Simon Peyton Jones' 
presentation 
WJ> "Wearing the hair shirt" [1] that in his opinion "Lazyness doesn't really 
WJ> matter".

i suggest you to write some large program like darcs and try to make
it as efficient as C++ ones. i'm doing sort of it, and i selected
Haskell primarily because it gives unprecedented combination of power
and safety due to its strong but expressive type system, higher-order
functions and so on. i also use benefits of lazyness from time to
time, and may be even don't recognize each occasion of using lazyness.
but when i'm going to optimize my program, when i'm asking myself "why
it is slower than C counterparts?", the answer is almost exclusively
"because of lazyness". for example, i now wrote I/O library. are you
think that i much need lazyness here? no, but that i really need is
the highest possible speed, so now i'm fighting against lazyness even
more than usual :)

well, 80% of any program don't need optimization at all. but when i
write remaining 20% or even 5%, i don't want to fight against
something that can be easily fixed in systematic way. all other
widespread languages have _optional_, explicitly stated lazyness in
form of callable blocks, even the Omega goes in this way. and i'm
interested in playing with such Haskell dialect in order to see how my
programming will change if i need to explicitly specify lazyness when
i need it, but have strictness implicitly. i think that newcomers from
other languages who wants to implement real projects instead of
experimenting will also prefer strict Haskell

you may hear that last days Haskell become one of fastest language in
the Shootout. why? only because all those programs was rewritten to be
strict. it was slow and hard process. and adding preprocessor that
makes all code strict automagically will allow to write efficient
Haskell programs without reading fat manuals

each laguage feature has its time. 15 years ago i could substantially
speed up C program by rewriting it in asm. Now the C compilers in most
cases generate better code than i can. moreover, strict FP languages
now are ready to compete with gcc. But lazy languages are still not
compiled so efficient that they can be used for time-critical code.
so, if we don't want to wait another 10 years, we should implement
easier ways to create strict programs. if you think that lazy
programming is great, you can show this in shootout or by showing me
the way to optimize code of my real programs. i'm open to new
knowledge :)

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re[2]: Comment Syntax

2006-02-03 Thread Bulat Ziganshin
Hello John,

Friday, February 03, 2006, 3:39:38 AM, you wrote:
>> Got a unicode-compliant compiler?

JM> sure do :)

JM> but it currently doesn't recognize any unicode characters as possible
JM> operators.

are you read this? :)

>   Log:
>   Add support for UTF-8 source files
> 
>   GHC finally has support for full Unicode in source files.  Source
>   files are now assumed to be UTF-8 encoded, and the full range of
>   Unicode characters can be used, with classifications recognised
using
>   the implementation from Data.Char.  This incedentally means that
only
>   the stage2 compiler will recognise Unicode in source files, because
I
>   was too lazy to port the unicode classifier code into libcompat.
> 
>   Additionally, the following synonyms for keywords are now
recognised:
> 
> forall symbol (U+2200)forall
> right arrow   (U+2192)->
> left arrow(U+2190)<-
> horizontal ellipsis   (U+22EF)..
> 
>   there are probably more things we could add here.
> 
>   This will break some source files if Latin-1 characters are being
used.
>   In most cases this should result in a UTF-8 decoding error.  Later
on
>   if we want to support more encodings (perhaps with a pragma to
specify
>   the encoding), I plan to do it by recoding into UTF-8 before
parsing.
> 
>   Internally, there were some pretty big changes:
> 
> - FastStrings are now stored in UTF-8
> 
> - Z-encoding has been moved right to the back end.  Previously we
>   used to Z-encode every identifier on the way in for simplicity,
>   and only decode when we needed to show something to the user.
>   Instead, we now keep every string in its UTF-8 encoding, and
>   Z-encode right before printing it out.  To avoid Z-encoding the
>   same string multiple times, the Z-encoding is cached inside the
>   FastString the first time it is requested.
> 
>   This speeds up the compiler - I've measured some definite
>   improvement in parsing at least, and I expect compilations
overall
>   to be faster too.  It also cleans up a lot of cruft from the
>   OccName interface.  Z-encoding is nicely hidden inside the
>   Outputable instance for Names & OccNames now.
> 
> - StringBuffers are UTF-8 too, and are now represented as
>   ForeignPtrs.
> 
> - I've put together some test cases, not by any means exhaustive,
>   but there are some interesting UTF-8 decoding error cases that
>   aren't obvious.  Also, take a look at unicode001.hs for a demo.


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re[2]: Priorities

2006-02-03 Thread Bulat Ziganshin
Hello Tomasz,

Friday, February 03, 2006, 10:52:22 AM, you wrote:

>> Personally, I'm not sure about caseless underscore, concurrency, natural
>> numbers and parallel list comprehensions.

TZ> The design of Haskell was so great, that we could add concurrency as
TZ> a library without introducing any problems... but we have
TZ> concurrency in the standard anyway...

concurrency should go into the Standard Library specification. there
is just nothing to say about this in the _language_ standard



-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Unary operators [was: Re: ~ patterns]

2006-02-03 Thread Bulat Ziganshin
Hello Benjamin,

Friday, February 03, 2006, 2:29:47 AM, you wrote:

(+ x) --->> (? + x)

i like this idea! but i tink that it's too late for such incompatible change :(

really, unary operators can be added to language without any troubles.
we need only to prohibit using of the same symbol for unary and binary
operators:

unary 9 #

#n = n-1

f = #1-1

we can even allow prefix and postfix operators as long as they all have
different names


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re[2]: give equal rights to types and classes! :)

2006-02-03 Thread Bulat Ziganshin
Hello Wolfgang,

Friday, February 03, 2006, 2:22:17 AM, you wrote:

>> 1) significantly simplifies declarations using typeclasses. i
>> was seriously bitten by those huge declarations, and think that
>> simplification in this area will lead to much wider use of type
>> classes by the ordibary users (like me :) .

WJ> "Simple" doesn't necessarily mean "small".  In my opinion, your smaller 
type 
WJ> declarations are confusing since they mix up classes and types.  Classes 
and 
WJ> types are two totally different things.  A class corresponds to a set of 
WJ> types, not to a single type, and a class has methods which a type has not.

type have the same methods, they are just not expressed directly. are
you know history of Array -> IArray change? functions "(!)",
"bounds" and so on in magic way round to class methods. if my idea was
incorporated in Haskell, this change don't require even changing
signatures of most functions working with arrays - just Array type
become Array interface, what a much difference?

Now i'm trying to generalize my functions parameters/results to type
classes instead of single types. for example, getFileSize function can
return any numeric value, be it Integer, Word or Int64. This,
naturally, results in those long and awkward signatures. Allowing to
write type of result as just "Integral" makes signature smaller
and more understandable for me:

getFileSize :: Stream Monad h -> Monad Integral


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


concurrency (was Re: Priorities)

2006-02-03 Thread Ross Paterson
On Fri, Feb 03, 2006 at 10:20:01AM +0100, Tomasz Zielonka wrote:
> Even if concurrency is part of Haskell', it should still be clear
> that it doesn't affect the definition of non-concurrent Haskell' subset
> at all (is that true?). For example, all pure functions will be entirely
> thread-safe.

As another example, Ben Rudiak-Gould recently pointed out that the
inclusion of stToIO breaks threaded state reasoning for ST, e.g.
readSTRef won't necessarily get what your last writeSTRef wrote (because
the region might be RealWorld, with other threads modifying it).

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Priorities

2006-02-03 Thread Tomasz Zielonka
On Fri, Feb 03, 2006 at 08:40:27AM -, Simon Peyton-Jones wrote:
> | Some experts (like Hans Boehm) argue, that concurrency can't be added
> to
> | the language as a library.
> | http://www.hpl.hp.com/techreports/2004/HPL-2004-209.pdf
> | 
> | This is true for many imperative programming languages. Haskell seems
> | to be an exception:
> |
> http://www.haskell.org//pipermail/glasgow-haskell-users/2005-December/00
> 9417.html
> 
> The interface can be a library, but (a) what libraries are available is
> part of the language definition and (b) it's hard to build a good
> implementation without runtime support.  And the nature of the runtime
> support depends on what the library interface is.

I forgot about runtime support. My point is that you we able to
introduce a library/runtime support without changing the semantics of
the language, and it works well.

> So a programmer asks "can I write my Haskell' program using
> concurrency?".  To answer that question, concurrency needs to be
> specified as part of Haskell', just as (say) Integer and its operations
> do.  [Of course, we can choose not to; and then Haskell' programs will
> be single-threaded.]

Yes, you are right. I was not entirely serious in my argumentation ;-)
Even if concurrency is part of Haskell', it should still be clear
that it doesn't affect the definition of non-concurrent Haskell' subset
at all (is that true?). For example, all pure functions will be entirely
thread-safe.

Best regards
Tomasz

-- 
I am searching for programmers who are good at least in
(Haskell || ML) && (Linux || FreeBSD || math)
for work in Warsaw, Poland
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: fundeps syntax is ugly

2006-02-03 Thread Johannes Waldmann
Ian Lynagh wrote:

> Also, order is relevant in many situations with records, e.g.
> 
> data Foo = Foo { x :: Char, y :: Bool }
> 
> defines Foo :: Char -> Bool -> Foo as well as the corresponding pattern
> constructor

True. Of course the reason is, allowing both positional and named
notation for records is a design error :-)

But this is distracting from my main point:
using spaces for grouping in fundeps is ugly
because it looks like application.
The separator should be a comma.
-- 
-- Johannes Waldmann -- Tel/Fax (0341) 3076 6479/80 --
 http://www.imn.htwk-leipzig.de/~waldmann/ ---

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Priorities

2006-02-03 Thread John Meacham
On Fri, Feb 03, 2006 at 08:40:27AM -, Simon Peyton-Jones wrote:
> The interface can be a library, but (a) what libraries are available is
> part of the language definition and (b) it's hard to build a good
> implementation without runtime support.  And the nature of the runtime
> support depends on what the library interface is.

If we had a good standard poll/select interface in System.IO then we
actually could implement a lot of concurrency as a library with no
(required) run-time overhead. I'd really like to see such a thing get
into the standard. Well, mainly it would just be a really useful thing
to have in general. If others think it is a good idea I can try to come
up with a suitable API and submit it to the repo.

My main issue with actually requiring concurrency is that it implies
some very non-trivial runtime overhead. at least as implemented by ghc.
of course, since ghc already uses indirect functions for all of its
thunk evaluations, it effectivly gets the ability to do concurrency 'for
free'. But this is certainly not true of all run-time models. There was
an interesting paper on implementing abstract interpreters that showed
on modern architectures although indirect function calls only are 5-10%
of the instructions executed, they account for well more than half of
the time spent in a program. in ghc generated assembling I am guessing
they are more like 30-40% of calls (the fact that ghc gets such great
performance despite this is quite promising for its future! I hope a
common c-- back end can be developed and shared among haskell
implementations that is particularly good at optimizing the type of code
we like to produce. But I have limited myself to writing one compiler at
a time for the time being :) .) 

What I would really like to see come out of this process as it relates
to concurrency are:

the ability to write thread-safe (but not thread using) libraries
portably. which means MVars and foreign annotations but nothing more.

A nice, well thought out standardized poll/select/asynchronous IO
library as part of System.IO. this will fill a much needed gap between
full concurrency and synchronous IO which is currently a void and will
provide just enough run-time support for experimenting with portable
concurrency libraries.

a method of standardizing extensions independent of the language and
getting them approved as "official, optional features", concurrency is
really interesting and I'd hate to bog it down by forcing it to evolve
at the haskell standards pace :)


John


-- 
John Meacham - ⑆repetae.net⑆john⑈ 
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


RE: Priorities

2006-02-03 Thread Simon Peyton-Jones
| Some experts (like Hans Boehm) argue, that concurrency can't be added
to
| the language as a library.
| http://www.hpl.hp.com/techreports/2004/HPL-2004-209.pdf
| 
| This is true for many imperative programming languages. Haskell seems
| to be an exception:
|
http://www.haskell.org//pipermail/glasgow-haskell-users/2005-December/00
9417.html

The interface can be a library, but (a) what libraries are available is
part of the language definition and (b) it's hard to build a good
implementation without runtime support.  And the nature of the runtime
support depends on what the library interface is.

So a programmer asks "can I write my Haskell' program using
concurrency?".  To answer that question, concurrency needs to be
specified as part of Haskell', just as (say) Integer and its operations
do.  [Of course, we can choose not to; and then Haskell' programs will
be single-threaded.]

Simon
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime