[Haskell-cafe] Re: A question about functional dependencies and existential

2007-03-28 Thread Jean-Marie Gaillourdet
Hi Oleg and others,

[EMAIL PROTECTED] wrote:
 Jean-Marie Gaillourdet wrote:
 class T root pos sel | pos - root, root - sel where
f :: pos - sel - Bool
 instance T root (Any root) sel
 If that is correct, I don't understand why this instance should be to
 general, as every instantiation of root exactly determines the
 corresponding instantiation of Any root.
 
 The class T has two functional dependencies: pos - root and
 root-sel. I believe you are talking about the former whereas my
 previous message was talking about the latter.

But the same applies to the second functional dependency and the type
variable sel. Every instantiation of root determines the instantiation
of sel. And that forbids instance T Int (Any Int) Bool and instance T
Int (Any Int) Int inside the same scope, doesn't it?

At least, that is what I would like to express by those two fundeps.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Why the Prelude must die

2007-03-28 Thread Simon Marlow
I support both reducing the prelude to just a few commonly used combinators, and 
 requiring an explicit import Prelude.  In response to a couple of Stefan's points:


Stefan O'Rear wrote:


6. Dependency

Because every module imports the Prelude every module that the Prelude
depends on, mutually depends with the Prelude.  This creates huge
dependency groups and general nightmares for library maintainers.


Not a problem in practice, for GHC at least: all modules below the Prelude use 
-fno-implicit-prelude, there's no recursive dependency.  Also, if the Prelude 
were smaller, it would be much lower in the dependency tree which would make 
life easier.



7. Monolithicity

Every module the Prelude uses MUST be in base.  Even if packages could
be mutually recursive, it would be very difficult to upgrade any of
the Prelude's codependents.


Not necessarily - the Prelude itself doesn't have to be in base.  If we split up 
base, then Prelude would likely have to be in a separate package.  Haskell' will 
need a separate Prelude, so the Haskell 98 Prelude will need to move to the 
haskell98 package.


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


Re: [Haskell-cafe] Newbie: a parser for a list of objects?

2007-03-28 Thread Dmitri O.Kondratiev

Daniel,
I am still trying to figure out the order of function applications in the
parser returning list of objects (I attached again the code to the end of
this message for convenience).

You wrote:
(*) associates to the right, hence
p * (p * (p * (... * (p * succeed [])...)))

I don't understand where (p * succeed []) comes from?

Yet, if the order is as you describe, everything goes well, for example:

comp1 = dig * dig   has type  - Parser char (char, char)
comp2 = dig * (succeed [])  has type  - Parser char (char, [a])
pl1 = comp2 `build` (uncurry (:)) has type - Parser char (char, [char])

At first run
(succeed []) `alt` ((p * pList p) `build` (uncurry (:)))

should be:
[] ++  ((p * pList p) `build` (uncurry (:)))

so how we get:
(p * succeed []) ?

Thanks,
Dima

---
module MyParser where

import Data.Char

type Parse a b = [a] - [(b, [a])]

none :: Parse a b
none  = \inp - []

succeed :: b - Parse a b
succeed val = \inp - [(val, inp)]

spot :: (a - Bool) - Parse a a
spot p = \inp - case inp of
  [] - []
  (x:xs) - if (p x) then [(x, xs)] else []

alt :: Parse a b - Parse a b - Parse a b
alt p1 p2 = \inp - p1 inp ++ p2 inp

bracket = spot (=='(')
dash = spot (== '-')
dig = spot isDigit
alpha = spot isAlpha

infixr 5 *

(*) :: Parse a b - Parse a c - Parse a (b, c)
(*) p1 p2 = \inp - [((x,y), rem2) |(x, rem1) - p1 inp, (y, rem2) - p2
rem1]


build :: Parse a b - (b - c) - Parse a c
build p f = \inp - [ (f x, rem) | (x, rem) - p inp]

pList :: Parse a b - Parse a [b]
pList p = (succeed []) `alt`
((p * pList p) `build` (uncurry (:)))

comp1 = dig * dig
comp2 = dig * (succeed [])
pl1 = comp2  `build` (uncurry (:))

test = pList dig

On 3/28/07, Daniel Fischer [EMAIL PROTECTED] wrote:


Am Dienstag, 27. März 2007 12:15 schrieb Dmitri O.Kondratiev:
 Thanks Daniel!
 Things are getting more in shape, yet I still can not fully comprehend
the
 expression:

 ((p * pList p) `build` (uncurry (:)))

 where

  (*) :: Parse a b - Parse a c - Parse a (b, c)
  (*) p1 p2 inp = [((x,y), rem2) |(x, rem1) - p1 inp, (y, rem2) - p2
 rem1]

  build :: Parse a b - (b - c) - Parse a c
  build p f inp = [ (f x, rem) | (x, rem) - p inp]

 So in fact recursive application:

 p * pList p

 should unfold in something like:

 ((p * p) * p) * p ...

(*) associates to the right, hence
p * (p * (p * (... * (p * succeed [])...)))


 and *all*  iterations of

 p * pList p

 will be done *before* 'build' will be applied?

 Correct?

Think so. Though it might be conceivable that 'build' would be partially
applied before.
After p has parsed the first item x1, leaving the remainder rem of the
input,
we can see that the result will be
[(x1:lst,rem2) | (lst,rem2) - pList p rem]
and we know that pList p never fails, due to 'succeed []', so that would
be
more efficient than constructing and destroying a lot of pairs.
I've no idea whether a compiler would do that transformation, though I'd
be
interested to know.

 Thanks,
 Dima

Cheers,
Daniel


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


Re: [Haskell-cafe] Re: Why the Prelude must die

2007-03-28 Thread Andrzej Jaworski
On blessed Wed Mar 28 05:52:03 EDT 2007 Simon Marlow wrote:

 I support both reducing the prelude to just a few commonly used combinators, 
 and 
   requiring an explicit import Prelude. (...)

So YOU are the GOD's angle with the sword!

And thus we leave the orchard for a battlefield. I really like this:-)

Holy regards,
-Andrzej

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


Re: [Haskell-cafe] Newbie: a parser for a list of objects?

2007-03-28 Thread Daniel Fischer
Am Mittwoch, 28. März 2007 11:57 schrieb Dmitri O.Kondratiev:
 Daniel,
 I am still trying to figure out the order of function applications in the
 parser returning list of objects (I attached again the code to the end of
 this message for convenience).

 You wrote:
 (*) associates to the right, hence
 p * (p * (p * (... * (p * succeed [])...)))

 I don't understand where (p * succeed []) comes from?

The final 'succeed []' comes from a) the definition of pList p as
pList p = succeed [] `alt` ((p * pList p) `build` (uncurry (:)))
plus b) the assumption that p should be a parser which doesn't succed on an 
empty input and that the input is finite (though the second point is not 
necessary).

Let us unfold a little:

pList dig 12ab
=== succeed [] 12ab ++ (((dig * pList dig) `build` (uncurry (:))) 
12ab)
=== [([],12ab)] ++ [('1' : ds,rem) | (ds,rem) - pList dig 2ab]
-- since dig 12ab = [('1',2ab)]
=== [([],12ab)] ++ [('1' : ds,rem) | (ds,rem) - (succed [] `alt` 
(((dig * pList dig) `build` 
(uncurry (:) 2ab]
=== [([],12ab)] ++ [('1' : ds,rem) | (ds,rem) - ([([],2ab)] ++ 
[('2' : ds2,rem2) | (ds2,rem2) - pList dig 
ab])]
=== [([],12ab),(1,2ab)] ++
[('1' : '2' : ds2,rem2) | (ds2,rem2) - (succeed [] `alt` 
(((dig * pList dig) `build` (uncurry (:) ab]
=== [([],12ab),(1,2ab)] ++
[('1' : '2' : ds2,rem2) | (ds2,rem2) - ([([],ab)] ++ 
(((dig * pList dig) `build` (uncurry (:))) ab))]
-- now 'dig' and hence 'dig * pList dig' fail on the input ab, 
thus
=== [([],12ab),(1,2ab),(12,ab)]

Hum, I find that a bit hard to read myself, so let's introduce an alias for 
'alt', call it (+) and a new combinator which joins (*) and 
'build (uncurry (:))' :
(:) :: Parser a b - Parser a [b] - Parser a [b]
p1 : p2 = \inp - [(x:ys,rem2)  | (x,rem1) - p1 inp, (ys,rem2) - p2 rem1]
-- or p1 : p2 = build (p1 * p2) (uncurry (:))

Then we have (because p1 : (p2 + p3) === (p1 : p2) + (p1 : p3))
pList p
=== succeed [] + (p : pList p)
=== succeed [] + (p : (succeed [] + (p : pList p)))
=== succeed [] + (p : succeed []) + (p : (p : pList p))
=== succeed [] + (p : succeed []) + (p : (p : (succeed [] + 
(p : pList p
=== succeed []
+ (p : succeed [])
+ (p : (p : succeed []))
+ (p : (p : (p : succeed [])))
+ (p : (p : (p : (p : pList p
and so on.
And when we request more p's than the input provides, pList p isn't reached 
anymore and recursion stops (e.g. with p = dig and input 123 or 123a45,
the last line will fail because it demands four digits from the beginning of 
the input, but there are only three).
If p would succeed on an empty input, e.g. p = succeed 1 or the input is an 
infinite list of successes for p, e.g. p = dig and input = cycle 123, the 
unfolding would never stop, producing an infinite list of results, but each 
of these results wolud come from a finite chain of p's ended by a 
'succeed []'.

So the order of evaluation of 
pList p input = (succeed [] + (p : pList p)) input
  = succeed [] input ++ (p : pList p) input
is
1. evaluate the first argument of (++), succeed [] input == [([],input)]
Since this is not _|_, we need also the second argument of (++), so
2. evaluate (p : pList p) input (to whnf first, more if required)
3. evaluate (++) as far as needed

2. is further split,
2.1. evaluate p input, giving a list of (obj,rem) pairs -- if that's empty, 
we're done, also if that produces _|_
2.2. (partially) evaluate pList p rem (goto 1.) giving a list of 
(objlist,rem2); [([],rem),([obj2],rem'),([obj2,obj3],rem'')...]
2.3. return the list of (obj:objlist,rem2) pairs


 Yet, if the order is as you describe, everything goes well, for example:

 comp1 = dig * dig   has type  - Parser char (char, char)
 comp2 = dig * (succeed [])  has type  - Parser char (char, [a])
 pl1 = comp2 `build` (uncurry (:)) has type - Parser char (char, [char])

pl1 has type Parser Char [Char] because 'uncurry (:)' has type (a,[a]) - [a]


 At first run
 (succeed []) `alt` ((p * pList p) `build` (uncurry (:)))

 should be:
 [] ++  ((p * pList p) `build` (uncurry (:)))

(succeed [] `alt` ((p * pList p) `build` (uncurry (: input
gives
[([],input)] ++ ((p * pList p) `build` (uncurry (:))) input

 so how we get:
 (p * succeed []) ?

 Thanks,
 Dima

Anytime,
Daniel

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


[Haskell-cafe] announcing new web-devel mailinglist

2007-03-28 Thread Marc Weber
It's done. The mailinglist is called web-devel hosted on haskell.org and
can be fond by haskell.org - mailinglists - a comprehensive list of ..
To subscribe goto
http://www.haskell.org/mailman/listinfo/web-devel

If you want to help administrating the list drop me a mail.

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


[Haskell-cafe] Re: Why the Prelude must die

2007-03-28 Thread David House

On 28/03/07, Simon Marlow [EMAIL PROTECTED] wrote:

I support both reducing the prelude to just a few commonly used combinators, and
  requiring an explicit import Prelude.


Just to clear things up: would you need to do an import Prelude to get
at these few commonly used combinators, or would the import pull in
the 'wider' Prelude, with a more expansive selection, more akin to the
current Prelude?

--
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] cost of modules

2007-03-28 Thread Simon Peyton-Jones
| I believe you are seeing a speed decrease, because GHC is not inlining
| functions as much when you split them into modules. If you add
| explicit inline statements, I think you should be able to get back to
| your original timings.

Generally speaking GHC will inline *across* modules just as much as it does 
*within* modules, with a single large exception.

If GHC sees that a function 'f' is called just once, it inlines it regardless 
of how big 'f' is.  But once 'f' is exported, GHC can never see that it's 
called exactly once, even if that later turns out to be the case.  This 
inline-once optimisation is pretty important in practice.

So: do not export functions that are not used outside the module (i.e. use an 
explicit export list, and keep it as small as possible).

Simon

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


Re: [Haskell-cafe] Re: Re: Why the Prelude must die

2007-03-28 Thread Neil Mitchell

Hi


 Regarding type variable naming, a few of my more hardware minded
 friends I've asked to try Haskell often tease me about the opaque type
 variable names in the Prelude--it seems greater consideration of type
 variable names in the Prelude might behoove new users.

I think that single letter names are very a good idea for most of the things
in the Prelude. 'a', 'b' etc. are good for very general things like the
basic classes (Eq, Num, etc) and for parametric functions (flip, (.), etc).
I also like the 'm' for Monads of all kinds, but I would suggest to
use 'mt' for monad transformers. For collections I think 'c' is nice
and 'k' for keys seems to be sort of standard, but I would like to propose
using 'e' as generic name for elements of collections, if there are more
element types, then 'e1', e2' etc.


Looking through the Hoogle logs, if people search for a multi-letter
type name, they are usually getting the wrong end of the stick. People
often search for:

char - bool

I don't think there is anything wrong with single letter type names,
unless you are making your types too complex.

Thanks

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


Re: [Haskell-cafe] Re: Can we do better than duplicate APIs? [was: Data.CompactString 0.3]

2007-03-28 Thread Robert Dockins


On Mar 28, 2007, at 2:44 PM, Benjamin Franksen wrote:


Robert Dockins wrote:
After taking a look at the Haddock docs, I was impressed by the  
amount of
repetition in the APIs. Not ony does Data.CompactString duplicate  
the

whole
Data.ByteString interface (~100 functions, adding some more for  
encoding
and decoding), the whole interface is again repeated another four  
times,

once for each supported encoding.


I'd like to mention that as maintainer of Edison, I face similar

difficulties.
The data structure interfaces have scores of functions and there  
are about

20
different concrete implementations of various sorts.  Even minor  
interface

changes require a lot of tedious editing to make sure that everything

stays

in sync.


But... you have the type of all functions nailed down in classes.  
Thus, even
if a change in the API means a lot of tedious work adapting the  
concrete

implementations, at least the compiler helps you to check that the
implementations will conform to the interface (class);


This is true.


and users have to
consult only the API docs, and not every single function in all 20
implementations. With ByteString and friends there is (yet) no common
interface laid down anywhere. All the commonality is based on  
custom and
good sense and the willingness and ability of the developers to  
make their

interfaces compatible to those of others.


One could use code
generation or macro expansion to alleviate this, but IMO the  
necessity to
use extra-language pre-processors points to a weakness in the  
language;

it
be much less complicated and more satisfying to use a language  
feature

that

avoids the repetition instead of generating code to facilitate it.


I've considered something like this for Edison.  Actually, I've  
considered
going even further and building the Edison concrete  
implementations in a

theorem prover to prove correctness and then extracting the Haskell

source.

Some sort of in-langauge or extra-language support for mechanicly

producing
the source files for the full API from the optimized core API  
would be

quite welcome.  Handling export lists,


How so? I thought in Edision the API is a set of type classes.  
Doesn't that

mean export lists can be empty (since instances are exported
automatically)?


No.  Edison allows you to directly import the module and bypass the  
typeclass APIs if you wish.  Also, some implementations have special  
functions that are not part of the general API, and are only  
available via the module exports.


One could make typeclasses the only way to access the main API, but I  
rather suspect there would be performance implications.  I get the  
impression that typeclass specialization is less advanced than  
intermodule inlining (could be wrong though).




haddock comments,


I thought all the documentation would be in the API classes, not in  
the

concrete implementations.


It is now, but I've gotten complaints about that (which are at least  
semi-justified, I feel).  Also, the various implementations have  
different time bounds which must documented in the individual  
modules.  Ideally, I'd like to have the function documentation string  
and the time bounds on each function in each concrete  
implementation.  I've not done this because its just too painful to  
maintain manually.




typeclass instances,
etc, are quite tedious.

I have to admit, I'm not sure what an in-language mechanism for doing
something like this would look like.  Template Haskell is an  
option, I
suppose, but its pretty hard to work with and highly non- 
portable.  It

also
wouldn't produce Haddock-consumable source files.  ML-style first  
class

modules might fit the bill, but I'm not sure anyone is seriously

interested

in bolting that onto Haskell.


As I explained to SPJ, I am less concerned with duplicated work when
implementing concrete data structures, as with the fact that there  
is still
no (compiler checkable) common interface for e.g. string-like  
thingies,

apart from convention to use similar names for similar features.



Fair enough.  I guess my point is that typeclasses (ad per Edison)  
are only a partial solution to this problem, even if you can stretch  
them sufficiently (with eg, MPTC+fundeps+whatever other extension) to  
make them cover all your concrete implementations.




Cheers
Ben



Rob Dockins

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



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


[Haskell-cafe] A wish for relaxed layout syntax

2007-03-28 Thread Benjamin Franksen
Hi,

I often run into the following issue: I want to write a list of lengthy
items like this

mylist = [
  quite_lengthy_list_item_number_one,
  quite_lengthy_list_item_number_two,
  quite_lengthy_list_item_number_three
]

With the current layout rules this is a parse error (at the closing
bracket). Normally I avoid this by indenting everything one level more as
in

mylist = [
quite_lengthy_list_item_number_one,
quite_lengthy_list_item_number_two,
quite_lengthy_list_item_number_three
  ]

but I think this is a little ugly.

Same issue comes up with parenthesized do-blocks, I would like to write

when (condition met) (do
  first thing
  second thing
)

So my wish is for a revised layout rule that allows closing brackets (of all
sorts: ']', ')', '}') to be on the same indent level as the start of the
definition/expression that contains the corresponding opening bracket.

Cheers
Ben

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


[Haskell-cafe] Re: Can we do better than duplicate APIs?

2007-03-28 Thread Benjamin Franksen
Robert Dockins wrote:
 Some sort of in-langauge or extra-language support for mechanicly
 producing
 the source files for the full API from the optimized core API  
 would be
 quite welcome.

Have you considered using DrIFT? IIRC it is more portable and easier to use
than TH.

 Handling export lists, 

 How so? I thought in Edision the API is a set of type classes.  
 Doesn't that
 mean export lists can be empty (since instances are exported
 automatically)?
 
 No.  Edison allows you to directly import the module and bypass the  
 typeclass APIs if you wish.

Ah, I didn't know that.

 Also, some implementations have special   
 functions that are not part of the general API, and are only  
 available via the module exports.

Ok.

 One could make typeclasses the only way to access the main API, but I  
 rather suspect there would be performance implications.  I get the  
 impression that typeclass specialization is less advanced than  
 intermodule inlining (could be wrong though).

No idea. Experts?

 haddock comments,

 I thought all the documentation would be in the API classes, not in  
 the
 concrete implementations.
 
 It is now, but I've gotten complaints about that (which are at least  
 semi-justified, I feel).  Also, the various implementations have  
 different time bounds which must documented in the individual  
 modules.  

Yes, I forgot about that. Hmmm.

 Ideally, I'd like to have the function documentation string   
 and the time bounds on each function in each concrete  
 implementation.  I've not done this because its just too painful to  
 maintain manually.

I can relate to that. The more so since establishing such time bounds with
confidence is not trivial even if the code looks simple. BTW, code
generation (of whatever sort) wouldn't help with that, right?

I wonder: would it be worthwhile to split the package into smaller parts
that could be upgraded in a somewhat less synchronous way? (so that the
maintenance effort can be spread over a longer period)

 I have to admit, I'm not sure what an in-language mechanism for doing
 something like this would look like.  Template Haskell is an  
 option, I
 suppose, but its pretty hard to work with and highly non- 
 portable.  It
 also
 wouldn't produce Haddock-consumable source files.  ML-style first  
 class
 modules might fit the bill, but I'm not sure anyone is seriously
 interested
 in bolting that onto Haskell.

 As I explained to SPJ, I am less concerned with duplicated work when
 implementing concrete data structures, as with the fact that there  
 is still
 no (compiler checkable) common interface for e.g. string-like  
 thingies,
 apart from convention to use similar names for similar features.
 
 Fair enough.  I guess my point is that typeclasses (ad per Edison)  
 are only a partial solution to this problem, even if you can stretch  
 them sufficiently (with eg, MPTC+fundeps+whatever other extension) to  
 make them cover all your concrete implementations.

Yes, and I think these problems would be worth some more research effort.

Besides, I dearly hope that we can soon experiment with associated type
synonyms...

Cheers
Ben

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


[Haskell-cafe] Re: Why the Prelude must die

2007-03-28 Thread Benjamin Franksen
mgsloan wrote:
 On 3/24/07, Vivian McPhail [EMAIL PROTECTED] wrote:

 I agree with Sven, but...

 What I want to push is a 'mathematically sound' numeric prelude.  A
proper
 numerical prelude should have bona fide mathematical obects like groups,
 rings, and fields underlying common numerical classes.  It would be
 edifying
 to the student who discovered that the particular data type he is using
is
 an inhabitant of a known class and can thus take advantage of known
 properties, presupplied as class methods.  Reasoning and communication
 about
 programs, data types, and functions would be enhanced.
 
 One problem with that is that the instances are often times not
 mathematically sound - Int and Double certainly aren't.

Int is algebraically sound as a factor ring Z/nZ with n=2**k, k the number
of bits (which could be implementation defined). Unfortunately the order
inherited from Integer is not compatible with the algebra...

Cheers
Ben

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


Re: [Haskell-cafe] A wish for relaxed layout syntax

2007-03-28 Thread Andrzej Jaworski
 mylist =
   [ foo, bar, baz,
 qux, quux, foo,
 bar, baz, qux ]

Good direction.
Perhaps you can also figure out how to replace the disturbing $ operator? 

-Andrzej

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


Re: [Haskell-cafe] Re: Can we do better than duplicate APIs?

2007-03-28 Thread Robert Dockins
On Wednesday 28 March 2007 17:08, Benjamin Franksen wrote:
 Robert Dockins wrote:
  Some sort of in-langauge or extra-language support for mechanicly
 
  producing
 
  the source files for the full API from the optimized core API
  would be
  quite welcome.

 Have you considered using DrIFT? IIRC it is more portable and easier to use
 than TH.

DrIFT only works on datatype declarations (AFAIK) and doesn't really cover the 
use cases in question.

[snip]

  haddock comments,
 
  I thought all the documentation would be in the API classes, not in
  the
  concrete implementations.
 
  It is now, but I've gotten complaints about that (which are at least
  semi-justified, I feel).  Also, the various implementations have
  different time bounds which must documented in the individual
  modules.

 Yes, I forgot about that. Hmmm.

  Ideally, I'd like to have the function documentation string
  and the time bounds on each function in each concrete
  implementation.  I've not done this because its just too painful to
  maintain manually.

 I can relate to that. The more so since establishing such time bounds with
 confidence is not trivial even if the code looks simple. BTW, code
 generation (of whatever sort) wouldn't help with that, right?

Well, I can't imagine any tool that would prove the bounds for me unless 
automatic proof techniques have improved a _lot_ in the last week or so ;-)

However, if I could record the bounds once somewhere for each implementation 
and then have them auto merged with the documentation for each function, that 
would be great.

 I wonder: would it be worthwhile to split the package into smaller parts
 that could be upgraded in a somewhat less synchronous way? (so that the
 maintenance effort can be spread over a longer period)

Perhaps, but that only amortizes the effort rather than reducing it.


[snip]

  As I explained to SPJ, I am less concerned with duplicated work when
  implementing concrete data structures, as with the fact that there
  is still
  no (compiler checkable) common interface for e.g. string-like
  thingies,
  apart from convention to use similar names for similar features.
 
  Fair enough.  I guess my point is that typeclasses (ad per Edison)
  are only a partial solution to this problem, even if you can stretch
  them sufficiently (with eg, MPTC+fundeps+whatever other extension) to
  make them cover all your concrete implementations.

 Yes, and I think these problems would be worth some more research effort.

Agreed.

 Besides, I dearly hope that we can soon experiment with associated type
 synonyms...

 Cheers
 Ben


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


Re: [Haskell-cafe] A wish for relaxed layout syntax

2007-03-28 Thread Andrzej Jaworski
  Perhaps you can also figure out how to replace the disturbing $ operator?

 Why is it disturbing?

It is not that I am short on dollar or Eurofobic;-)
It introduces sort of daub aesthetics to the code. Also for someone that puts 
strong
emphases on notation signs should have some semiotic responsibility and 
shouldn't shout at
you without having sufficient prominence.
I wouldn't use this arguments with Perl programmers of course.

Cheers
-Andrzej

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


Re: [Haskell-cafe] A wish for relaxed layout syntax

2007-03-28 Thread John Meacham
On Wed, Mar 28, 2007 at 10:21:08PM +0200, Benjamin Franksen wrote:
 Hi,
 
 I often run into the following issue: I want to write a list of lengthy
 items like this
 
 mylist = [
   quite_lengthy_list_item_number_one,
   quite_lengthy_list_item_number_two,
   quite_lengthy_list_item_number_three
 ]
 
 With the current layout rules this is a parse error (at the closing
 bracket). Normally I avoid this by indenting everything one level more as
 in
 
 mylist = [
 quite_lengthy_list_item_number_one,
 quite_lengthy_list_item_number_two,
 quite_lengthy_list_item_number_three
   ]
 
 but I think this is a little ugly.
 
 Same issue comes up with parenthesized do-blocks, I would like to write
 
 when (condition met) (do
   first thing
   second thing
 )
 
 So my wish is for a revised layout rule that allows closing brackets (of all
 sorts: ']', ')', '}') to be on the same indent level as the start of the
 definition/expression that contains the corresponding opening bracket.

this would be fairly simple by adding a rule to the parser grammer like
so

list := '[' item* ';'? ']'

as in, allow an optional semicolon before any bracketing closing token.


as for the other example, I tend to do

when (condition met) $ do
  first thing
  second thing

though, the semicolon thing above would allow the layout you want too.


John

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


Re: [Haskell-cafe] Re: Can we do better than duplicate APIs? [was: Data.CompactString 0.3]

2007-03-28 Thread Duncan Coutts
On Wed, 2007-03-28 at 20:44 +0200, Benjamin Franksen wrote:

 But... you have the type of all functions nailed down in classes. Thus, even
 if a change in the API means a lot of tedious work adapting the concrete
 implementations, at least the compiler helps you to check that the
 implementations will conform to the interface (class); and users have to
 consult only the API docs, and not every single function in all 20
 implementations. With ByteString and friends there is (yet) no common
 interface laid down anywhere. All the commonality is based on custom and
 good sense and the willingness and ability of the developers to make their
 interfaces compatible to those of others.

Remember that there's more to an API than a bunch of types. The type
class only ensures common types.

You must still rely on the good sense and ability of the developers to
ensure other properties like strictness, time complexity and simply what
the functions should do.

Duncan

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


Re: [Haskell-cafe] A wish for relaxed layout syntax

2007-03-28 Thread Greg Buchholz
Andrzej Jaworski wrote:
 Good direction.
 Perhaps you can also figure out how to replace the disturbing $ operator? 

Something out of Unicode? 

≬⊳⌁⋆☕⚡‣‸‡⁏•△▴◆◇◊◬◢◮♘♣♲♪◖▻▿轢

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


Re: [Haskell-cafe] A wish for relaxed layout syntax

2007-03-28 Thread Greg Buchholz
David House wrote:
 I see this a lot. My personal preference is:
 
 mylist =
  [ foo, bar, baz,
qux, quux, foo,
bar, baz, qux ]

 Or,

   mylist = [foo, bar , baz,
 qux, quux, foo,
 bar, baz , qux]

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


[Haskell-cafe] Re: A question about functional dependencies and existential

2007-03-28 Thread oleg

 class T root pos sel | pos - root, root - sel where
f :: pos - sel - Bool
 instance T root (Any root) sel

 But the same applies to the second functional dependency and the type
 variable sel. Every instantiation of root determines the instantiation
 of sel. And that forbids instance T Int (Any Int) Bool and instance T
 Int (Any Int) Int inside the same scope, doesn't it?

Indeed that is your intent, expressed in the functional dependency. It
may help to think of a class declaration as an `interface' and of the
set of instances as an `implementation' (of the type class). In the
example above, the class T root pos sel _declares_ a ternary
relation T and specifies some `constraints'. The set of instances of T
(in our example, there is only one instance) specifies the triples
whose set defines the relation T. In Herbrand interpretation, an
unground instance
instance C1 x y = C (Foo x) (Bar y)
corresponds to a set of instances where the free type variables are
substituted by all possible ground types provided the instance
constraints (such as C1 x y) hold. In our example, an unground
instance |instance T root (Any root) sel| is equivalent to a set of
ground instances where |root| and |sel| are replaced with all possible
ground types. Including
instance T Int (Any Int) Bool
instance T Int (Any Int) Int
These two instances are in the model for 
`instance T root (Any root) sel'. A set of instances, an
implementation of a type class, must satisfy the interface, that is,
constraints imposed by the class declaration, including the functional
dependency constraints. In our example, any implementation of T must
satisfy root - sel constraints. The above two instances show there
exists a model of T where the functional dependency is
violated. That's why both GHC 6.4 and Hugs reject the instance. Again,
it is a mystery why GHC 6.6 accepts it.

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


Re: [Haskell-cafe] A wish for relaxed layout syntax

2007-03-28 Thread Nicolas Frisby

I don't think that

aName =
 [ x
 , y
 , z
 ]

can be beat for adaptability (i.e. adding/removing/reorganizing
results or _especially_ renaming the declaration). Doesn't do so hot
regarding vertical space though...

On 3/28/07, Greg Buchholz [EMAIL PROTECTED] wrote:

David House wrote:
 I see this a lot. My personal preference is:

 mylist =
  [ foo, bar, baz,
qux, quux, foo,
bar, baz, qux ]

 Or,

   mylist = [foo, bar , baz,
 qux, quux, foo,
 bar, baz , qux]

___
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] Re: A question about functional dependencies and existential

2007-03-28 Thread Nicolas Frisby

A wee bit off topic... but bear with me.

Oleg points out a distinction between declaring a class with
functional dependencies and implementing a class with functional
dependencies. Judging from my experience, it might behoove those
wrestling with type classes and FDs to emphasize that the class
declaration also merely declares the functional dependencies and does
not guarantee them as type-level functions. Moreover, instances
implementing the class implement the functional dependencies as well.
However, just because GHC accepts the instances as satisfying the
functional dependencies, it doesn't necessarily guarantee that the
functional dependencies can be aggressively used to resolve
polymorphism--let me elaborate on this last point. Consider

class C a b | a - b where
   foo :: a - b

instance C Int Int where
   foo = id
instance Num a = C Bool a where
   foo _ = 3

GHC 6.7.20070214 accepts this code with fglasgow-exts and undecidable
instances. I usually read the functional dependencies as a determines
b (and I suspect many other people do as well). Unfortunately, that
is not the guaranteed by the functional dependency analyzer. What is
guaranteed is that any two instances of C do not together contradict
the functional dependencies. Given C Bool x, I cannot infer what x is,
though I had thought that a determines b.

When I was exercising my prefrontal Olegial cortex in writing my own
static record library a la Hlist, I learned this lesson the hard way.
Hopefully this saves the reader some trouble.

Motto: appeasing the functional dependency analyzer DOES NOT mean
that the type class is actually a type function. Perhaps ATs do have
this quality? I'm not sure--but if they do I will definitely be a fan.

On 3/28/07, [EMAIL PROTECTED] [EMAIL PROTECTED] wrote:


 class T root pos sel | pos - root, root - sel where
f :: pos - sel - Bool
 instance T root (Any root) sel

 But the same applies to the second functional dependency and the type
 variable sel. Every instantiation of root determines the instantiation
 of sel. And that forbids instance T Int (Any Int) Bool and instance T
 Int (Any Int) Int inside the same scope, doesn't it?

Indeed that is your intent, expressed in the functional dependency. It
may help to think of a class declaration as an `interface' and of the
set of instances as an `implementation' (of the type class). In the
example above, the class T root pos sel _declares_ a ternary
relation T and specifies some `constraints'. The set of instances of T
(in our example, there is only one instance) specifies the triples
whose set defines the relation T. In Herbrand interpretation, an
unground instance
instance C1 x y = C (Foo x) (Bar y)
corresponds to a set of instances where the free type variables are
substituted by all possible ground types provided the instance
constraints (such as C1 x y) hold. In our example, an unground
instance |instance T root (Any root) sel| is equivalent to a set of
ground instances where |root| and |sel| are replaced with all possible
ground types. Including
instance T Int (Any Int) Bool
instance T Int (Any Int) Int
These two instances are in the model for
`instance T root (Any root) sel'. A set of instances, an
implementation of a type class, must satisfy the interface, that is,
constraints imposed by the class declaration, including the functional
dependency constraints. In our example, any implementation of T must
satisfy root - sel constraints. The above two instances show there
exists a model of T where the functional dependency is
violated. That's why both GHC 6.4 and Hugs reject the instance. Again,
it is a mystery why GHC 6.6 accepts it.

___
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] A question about functional dependencies

2007-03-28 Thread Matthew Brecknell
[EMAIL PROTECTED]:
 [...] The above two instances show there
 exists a model of T where the functional dependency is
 violated. That's why both GHC 6.4 and Hugs reject the instance. Again,
 it is a mystery why GHC 6.6 accepts it.

Actually, GHC 6.6 does reject cases like the one discussed in this
thread, but the check is not performed at the point of instance
declaration. Instead, it is deferred until the point of use. For
example:

 {-# OPTIONS_GHC -fglasgow-exts -fallow-undecidable-instances #-}
 
 data Any a = Any
 
 class Foo a b | a - b where foo :: a - b
 instance Foo (Any a) b where foo = undefined
 
 test1 :: Char
 test1 = foo (Any :: Any Int)

GHC 6.6 compiles the above without error. But add this:

 test2 :: Bool
 test2 = foo (Any :: Any Int)

And we get:

Couldn't match expected type `Char' against inferred type `Bool'
When using functional dependencies to combine
  Foo (Any Int) Bool, arising from use of `foo' at fd.hs:16:8-27
  Foo (Any Int) Char, arising from use of `foo' at fd.hs:13:8-27

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


[Haskell-cafe] ANNOUNCE: binary 0.3 - bigger, better, faster

2007-03-28 Thread Lennart Kolmodin

Greetings friends!

I'm pleased to announce binary 0.3!

The 'binary' package provides efficient serialization of Haskell values 
to and from lazy ByteStrings. ByteStrings constructed this way may then 
be written to disk, written to the network, or further processed (e.g. 
stored in memory directly, or compressed in memory with zlib or bzlib).


In total 14 people have contributed code and many more given feedback 
and cheerleading on [EMAIL PROTECTED] Thanks to all of you!


It's available through Hackage:
  tarball: 
http://hackage.haskell.org/packages/archive/binary/binary-0.3.tar.gz

  darcs:darcs get http://darcs.haskell.org/binary
  homepage: http://www.cse.unsw.edu.au/~dons/binary.html

It's been a while since the last release of binary [1] the 25th of 
January earlier this year. Lets have a look of what's changed since then:


API additions
-

The first thing you're going to notice that differs is the polished API. 
Being used by more people now than it was in January, we've added 
features that where missing before. More functions has been added to the 
Get/Put monads giving information over bytes read, remaining bytes etc 
for whenever you need to do custom serialization. You can now also read 
and write words in host endian order.


Instances has been added to handle Double, Float and Ratio.

Performance
---

Decoding speed has been tuned by a rewrite and is currently about half 
the speed of the lightning fast encoding.


Don't hesitate to give feedback on #haskell or by mail, we've always got 
time for a chat :)


The Binary Strike Force,
Lennart Kolmodin
Duncan Coutts
Don Stewart
Spencer Janssen
David Himmelstrup
Björn Bringert
Ross Paterson
Einar Karttunen
John Meacham
Ulf Norell
Tomasz Zielonka
Stefan Karrmann
Bryan O'Sullivan
Florian Weimer

 [1] http://article.gmane.org/gmane.comp.lang.haskell.general/14800

--
The only thing that interferes with my learning is my education.
-- Albert Einstein
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe