Re: Export lists in modules

2006-02-28 Thread Malcolm Wallace
Johannes Waldmann [EMAIL PROTECTED] wrote:

 For reference, in Java, ...  there's nice syntactic sugar for looping
 over collections:  CollectionE c; for (E item : c) { ... }
 I'd say this is an example of moving away from a left-biased
 representation, or at least freeing the programmer from having
 to think about it).

In Haskell, this is called 'fmap'.  :-)

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


Re[2]: overlapping instances and constraints

2006-02-28 Thread Bulat Ziganshin
Hello John,

Tuesday, February 28, 2006, 4:23:24 AM, you wrote:

 i had plans to propose the same and even more:
 
 instance C2 a b | a/=b

JM I was thinking it would be all kinds of useful if we had two predefined
JM classes

JM class Eq a b
JM class NEq a b

JM where Eq has instances exactly when its two types are equal and NEq has
JM instances exactly when its two types are not equal.

JM Eq should be straightforward to implement, declaring any type
JM automatically creates its instances. (sort of an auto-deriving). NEq
JM might be more problematic as that would involve a quadratic number of
JM instances so its implementation might need to be more special. but
JM perhaps we can do with just 'Eq'.

with 'Eq' class we can't do anything that is impossible without it
:)))

the whole devil is to make general instance NON-OVERLAPPING with
specific one by EXPLICITLY specifying EXCLUSIONS with these /= rules:

class Convert a b where
  cvt :: a-b

instance Convert a a where  -- are we need Eq here? :)
  cvt = id

instance (NEq a b) = Convert a b where
  cvt = read.show



... yes, i recalled! my proposal was to allow ! in instance headers:

instance C Int where ...
instance (!Int a, Integral a) = C a where ...
instance (!Integral a, Enum a) = C a where ...

adding your Eq class, it will be all we can do on this way

interesting, that the language theoretics can say about decidability,
soundness, and so on of this trick? :)

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: overlapping instances and constraints

2006-02-28 Thread Claus Reinke

instance C2 a b | a/=b


I was thinking it would be all kinds of useful if we had two predefined
classes

class Eq a b
class NEq a b

where Eq has instances exactly when its two types are equal and NEq has
instances exactly when its two types are not equal.


   class Eq a b
   instance Eq a a

   class NEq a b
   instance Fail a = NEq a a
   instance NEq a b

   class Fail all -- no instances

I think I first saw that class Fail trick in an HList talk. but having those
instances doesn't help if they are not used (eg, by following instance
constraints, to aid in overlap resolution, or to confirm FDs; or simply
because the system doesn't use the fact that Fail never has instances).
Even just extending Eq/NEq to type-level predicates (with a 3rd,
functionally dependent parameter) runs into trouble.

I'd prefer to extend the language so that those uses become expressible,
but for the short term, it'd be nice if the predicates _and_ their uses
were built-in. hence the special syntax to indicate that this predicate is
actually looked at when checking the instance.

cheers,
claus


Eq should be straightforward to implement, declaring any type
automatically creates its instances. (sort of an auto-deriving). NEq
might be more problematic as that would involve a quadratic number of
instances so its implementation might need to be more special. but
perhaps we can do with just 'Eq'.

   John

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


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


Re: Export lists in modules

2006-02-28 Thread Johannes Waldmann
Malcolm Wallace wrote:
 Johannes Waldmann [EMAIL PROTECTED] wrote:

 For reference, in Java, ...  there's nice syntactic sugar for looping
 over collections:  CollectionE c; for (E item : c) { ... }

 In Haskell, this is called 'fmap'.  :-)

OK, then show me an instance Functor Set so that I can use it :-)
-- 
-- 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: Export lists in modules

2006-02-28 Thread Johannes Waldmann
Cale Gibbard wrote:

 important point is that the elements and structure of the collection
 are being constructed one at a time as you iterate over it, and they
 are easily garbage collected as soon as you're done with them. 

OK, I kind of buy that argument. Though the very word deforestation
indicates that it might work for structures other than left-biased lists...
-- 
-- 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: Export lists in modules

2006-02-28 Thread Malcolm Wallace
Johannes Waldmann [EMAIL PROTECTED] wrote:

  In Haskell, this is called 'fmap'.  :-)
 
 OK, then show me an instance Functor Set so that I can use it :-)

instance Function Set where
fmap = Data.Set.mapMonotonic

Ok, so this introduces a precondition on the function being mapped, so
there is a proof obligation on the programmer.

But if contexts-on-datatypes worked correctly,

data Set a = Ord a = 

then even the real map from Data.Set:

map :: (Ord a, Ord b) = (a - b) - Set a - Set b

could be an instance method of Functor.  (Because the Ord constraints
would be packaged inside the Set type, rather than needing to be
explicit.)

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


instance Functor Set, was: Re: Export lists in modules

2006-02-28 Thread Johannes Waldmann
Malcolm Wallace wrote:

 But if contexts-on-datatypes worked correctly,
 
 data Set a = Ord a = 
 
 then even the real map from Data.Set:
 
 map :: (Ord a, Ord b) = (a - b) - Set a - Set b
 
 could be an instance method of Functor. 

I'd love that. But I don't quite understand:
do you think this is/should be possible with:
current Haskell? Haskell-Prime? Current ghc (what extensions)?
-- 
-- 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: realToFrac issues

2006-02-28 Thread Lennart Augustsson

Cale Gibbard wrote:

This change means that Rational is no longer a field. It makes me feel
uneasy at least. Should we really expect realToFrac to propagate those
values? Look at its type:
realToFrac :: (Real a, Fractional b) = a - b
Nothing about the Fractional class would seem to indicate that NaN and
+-Infinity should be representable. In fact, it just looks like the
basic field operations, and fields don't tend to have such elements
(not that we require the field axioms to hold for every instance).


I know for a fact that the Ratio type excludes 1%0 and 0%0 from the
allowed values by design rather than by mistake.  I discussed it with
Joe Fasel many years ago, and he convinced me it was a bad idea.

But I admit that the realToFrac argument carries some weight, even
if I had never even thought about the problem before.

-- Lennart


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


Re: instance Functor Set, was: Re: Export lists in modules

2006-02-28 Thread Malcolm Wallace
  But if contexts-on-datatypes worked correctly,
  
  data Set a = Ord a = 
  
  then even the real map from Data.Set:
  
  map :: (Ord a, Ord b) = (a - b) - Set a - Set b
  
  could be an instance method of Functor. 
 
 I'd love that. But I don't quite understand:
 do you think this is/should be possible with:
 current Haskell? Haskell-Prime? Current ghc (what extensions)?

It is not possible currently, because of the H'98 language definition.
I do think it would be nice to fix this in Haskell-prime.  However,
although the idea is somewhat related to Polymorphic Components
  http://hackage.haskell.org/trac/haskell-prime/wiki/PolymorphicComponents
there is no specific proposal about this issue on the wiki.  (It was
mentioned on some mailing list in the last couple of months, but I can't
find the thread now.)

By working correctly I mean that: it is a wart in Haskell'98 that you
can declare a datatype to require some class constraints on contained
elements, but that these extra constraints do not really buy you any
expressive power.  They just force you to repeat the same context decl
on every function that uses such a type.  Ideally, the data decl should
be more like an alias, capturing the constraints as part of the
semantics associated with the type, so that you don't need to mention
the constraints at every usage location of the type.

Of course, there are some details to work out, about where you can
validly omit the constraints, and where they are still required.

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


Re[2]: overlapping instances and constraints

2006-02-28 Thread Bulat Ziganshin
Hello Claus,

Tuesday, February 28, 2006, 1:54:25 PM, you wrote:

CR class NEq a b
CR instance Fail a = NEq a a
CR instance NEq a b

i think that this definition just use ad-hoc overlapping instances
resolution mechanism that we want to avoid :)))

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


RE: Export lists in modules

2006-02-28 Thread Simon Marlow
On 28 February 2006 13:37, Lennart Augustsson wrote:

 John Meacham wrote:
 
 I mean, even a for loop in haskell is done as
 mapM action [0..10]
 
 I'd say _most_ uses of lists are deforested away because they are
 used to express control and dataflow and arn't actually used as
 persistant structures.
 
 Yes, they are optimized away when ghc actually works. :)  At the
 moment this seems to be broken (try length[1..n] in 6.4.1).

Known bug (well, known since a few weeks ago at least).

http://cvs.haskell.org/trac/ghc/ticket/683

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


Re: [Haskell'-private] pragmas and annotations (RE: the record system)

2006-02-28 Thread Malcolm Wallace
Simon Marlow [EMAIL PROTECTED] wrote:

 How does ENCODING work for a UTF-16 file, for example?
 We don't know the file is UTF-16 until we read the ENCODING pragma,
 and we can't read the ENCODING pragma because it's in UTF-16. 

Use the same type of heuristic as XML uses (for instance).

  * If the first three bytes of the file are {-#, then keep reading in
ASCII/Latin-1/whatever until you discover an ENCODING decl (or not).

  * If the first six bytes of the file are one of the two possible
UTF-16 representations of {-#, then assume UTF-16 with that
byte-encoding until we find the ENCODING decl.  (A missing decl in
this case would be an error.)

  * If the first twelve bytes of the file are a UCS-4 representation of
{-# then ... you get the picture.

  * For UTF-16 and UCS-4 variations, you must also permit the file to
begin with an optional byte-order mark (two or four bytes).

  * Otherwise, there is no ENCODING pragma, so assume the implementation
default of {ASCII, Latin-1, UTF-8, ...}.

I know it's pretty horrible, but it seems to work in practice for the
XML people.  In practice, the ENCODING decl is most needed for those
that have ASCII as a subset - one could argue that the heuristic tells
you the UTF-16 and UCS-4 variations without needing a pragma.  (But
then, how would you guarantee that the first three characters in the
file must be {-# ?)

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


Re: [Haskell'-private] pragmas and annotations (RE: the record system)

2006-02-28 Thread kahl
Malcolm.Wallace wrote:

  (But then, how would you guarantee that the first three characters
  in the file must be {-# ?)

In particular, what do you propose for literate source?
(I hardly have any .hs files.)

As far as I can see,
it seems to be possible to get LaTeX to work with UTF8;
the (apparently not extremely active) ``Unicode TeX project'' Omega
apparently started out with ``16-bit Unicode'' (http://omega.enstb.org/)
and now turned to 31-bit characters (http://omega.cse.unsw.edu.au/omega/),
and the future may of course bring us other variants...


(Isn't it great that we can add a new dimension to Wadler's law
 by discussing character encodings?  ;-)


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


Re: realToFrac issues

2006-02-28 Thread Cale Gibbard
On 28/02/06, John Meacham [EMAIL PROTECTED] wrote:
 On Tue, Feb 28, 2006 at 12:44:04AM -0500, Cale Gibbard wrote:
  I'm almost scared to ask: does this mean we need negative zero as well?

 good point. probably.

  This change means that Rational is no longer a field. It makes me feel
  uneasy at least. Should we really expect realToFrac to propagate those
  values? Look at its type:
  realToFrac :: (Real a, Fractional b) = a - b
  Nothing about the Fractional class would seem to indicate that NaN and
  +-Infinity should be representable. In fact, it just looks like the
  basic field operations, and fields don't tend to have such elements
  (not that we require the field axioms to hold for every instance).

 It makes me uneasy too. Perhaps we can come up with something better.

  I personally don't see any reason that realToFrac should propagate the
  special error condition values of IEEE floating point types. Given its
  type, I'd expect it to throw an exception.

 well, the main reason is that it is the only way we have to convert
 between various floating point types. If we can come up with another
 mechanism then perhaps that is a better solution, but it is not at all
 obvious to me what that other mechanism would be.

How about,
toRealFloat :: (RealFloat a, RealFloat b) = a - b
toRealFloat = uncurry encodeFloat . decodeFloat
Presently, this doesn't quite work, but that's due to the inability of
encodeFloat to produce pairs which mean NaN and -0. If we extend its
codomain a bit to include those, that would seem fine. It would seem
to me that if we want a conversion between IEEE floating point types,
then it should be somewhere around here in the hierarchy anyway.

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


Re: the MPTC Dilemma (please solve)

2006-02-28 Thread Claus Reinke

You addressed this to me -- but I'm an advocate for rather conservative
extensions whereas you are calling for extensions that go beyond what
any current implementation can do.


generally, that may be true,-) but in this specific case, I was just asking 
for an effort to document the differences in current handling of extended
Haskell in hugs and ghc, by collecting test cases such as those I included. 

whether or not the haskell' process manages to help eradicate those 
differences is another matter, but collecting them seems a useful basis 
for decisions, hence a task rather than a proposal. I addressed that to 
you because (a) I was hoping this more moderate approach would be 
down your alley and (b) because you have a stake in this at ghc hq, 
and probably would want to collect the test cases for possible fixing.


I guess I will create the ticket myself, but if no committee member
or implementer has a stake in it, that won't do much good..


Anyway, there is already a ticket for overlapping instances, I think --
why don't you just add to that.


that might work. apart from the fact that I really, really hate the 
braindead wiki markup processor, especially when editing through

that tiny ticket change field instead of loading up text. I went through
that experience once, when Isaac suggested the same for my labels
proposal - I don't want to have to do that again.


If you send me Wiki-marked-up text I'll gladly paste it in for you.


perhaps I'll just restrict myself to attaching my example code to
some ticket (are guests allowed to update attachments?). will see..

thanks,
claus

| -Original Message-
| From: Claus Reinke [mailto:[EMAIL PROTECTED]
| Sent: 25 February 2006 15:33
| To: Simon Peyton-Jones
| Cc: haskell-prime@haskell.org
| Subject: Re: the MPTC Dilemma (please solve)
| 
| | Is the behaviour of GHC with -fallow-undecidable-instances (and

| | -fcontext-stack) well-understood and specifiable?
| I would not say that it's well-specified, no.
| 
| to start improving that situation, could we please have a task ticket

| for document differences in unconstrained instance handling, then
| ask everyone to attach source examples showing such differences?
| [can guests attach code to task tickets?]
| 
| the hope being, of course, that implementations nominally providing

| the same feature will eventually converge on providing the same
| interpretation of all programs using that feature.
| 
| an example of the current oddities (at least they seem odd to me;):

| both hugs and ghc claim to resolve overlapping instances in favour
| of the most specific instance declaration. both claim that functional
| dependencies uniquely determine the range types from the domain
| types. but they do not agree on which programs to accept when
| we try to combine best-match with FDs.
| 
| I've already given an example where ghc allows me to define

| record selection, while hugs complains that the overlap violates
| the FDs.
| 
| I reported that as a hugs bug, because I think the best-match

| resolution of overlaps should ensure that the FD violation cannot
| happen, so the code should be valid. there are different ways to
| interpret FDs (something to check, or something to use), but it
| seemed that ghc was doing the right thing there. thread start:
| 
| http://www.haskell.org//pipermail/hugs-bugs/2006-February/001560.html
| 
| but after further experimentation, I'm not longer sure that ghc

| is doing the right thing for the right reasons. here is a tiny example
| of one of the disagreements:
| 
| {- ghc ok

|hugs Instance is more general than a dependency allows -}
| 
| class C a b | a - b

| instance C a b
| 
| so what is ghc doing there? is it going to guarantee that b will

| always be uniquely determined?
| 
| {- ghc ok

|hugs Instance is more general than a dependency allows -}
| 
| class C b | - b where c :: b

| instance C b where c = error b
| 
| safely m = m `CE.catch` print

| main = do
|   safely $ print $ (c::Int)
|   safely $ print $ (c::Bool)
|   safely $ print [id,c]
| 
| oh, apparently not. unless b is uniquely determined to be universally

| quantified, and the instantiations happen after instance selection.
| 
| {- ghc ok

|hugs Instance is more general than a dependency allows -}
| 
| class C b | - b where c :: b

| instance C b where c = error b
| 
| class D a where d :: a - String

| instance C a = D a where d a = a
| instance C Int = D Int where d a = Int
| 
| -- try at ghci prompt:  (d 1,d (1::Int))

| -- gives: (a,Int)
| 
| so that parameter of C isn't all that unique. at least not long enough

| to influence instance selection in D.
| 
| comments?
| 
| cheers,

| claus

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


Re: instance Functor Set, was: Re: Export lists in modules

2006-02-28 Thread Jim Apple
On 2/28/06, Johannes Waldmann [EMAIL PROTECTED] wrote:
 Malcolm Wallace wrote:

  But if contexts-on-datatypes worked correctly,
 
  data Set a = Ord a = 
 
  then even the real map from Data.Set:
 
  map :: (Ord a, Ord b) = (a - b) - Set a - Set b
 
  could be an instance method of Functor.

 I'd love that. But I don't quite understand:
 do you think this is/should be possible with:
 current Haskell? Haskell-Prime? Current ghc (what extensions)?

as Oleg:

{-# OPTIONS -fglasgow-exts #-}
{-# OPTIONS -fallow-undecidable-instances  #-}

module Map where

import qualified Data.Set

class MyMap f a b where
myMap :: (a - b) - f a - f b
instance (Functor f) = MyMap f a b where
myMap = fmap
instance (Ord a, Ord b) = MyMap Data.Set.Set a b where
myMap = Data.Set.map

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


Re: overlapping instances and constraints

2006-02-28 Thread Niklas Broberg
On 2/28/06, Ben Rudiak-Gould [EMAIL PROTECTED] wrote:
 Simon Peyton-Jones wrote:
  - A program that type checks can have its meaning changed by adding an
  instance declaration
 
  - Similarly adding import M() can change the meaning of a program (by
  changing which instances are visible
 
  - Haskell would need to be a lot more specific about exactly where
  context reduction takes place.

 I think all of these problems would go away if overlap was permitted within
 a module but forbidden across modules. Are there uses of overlapping
 instances for which this isn't flexible enough?

Certainly! In HSP [1] there is a class (simplified here)

class IsXML xml where
  toXML :: xml - XML

data XML = Element  | CDATA String

that deals with how things should be represented as XML. There are a
number of basic instances for this, such as

instance IsXML String where
 toXML = CDATA

instance (Show a) = IsXML a where
 toXML = toXML . show

The intention of the latter is to be a default instance unless another
instance is specified. These instances can be found in the base HSP
module, but the idea is that HSP users should be able to work with
their own datatypes and only need to define the translation into XML
via instanciating IsXML. This would have to be done in the user
modules, so overlap across module boundaries are essential for this to
work. :-)

/Niklas

[1] http://www.cs.chalmers.se/~d00nibro/hsp/
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: overlapping instances and constraints

2006-02-28 Thread Niklas Broberg
Claus Reinke wrote:
 most of us would be happy if instance contexts
 would be required to uniquely determine the instance to be
 chosen, a rather conservative extension of current practice.

I'm not so sure about the most of us, as you note yourself the
defaulting pattern is quite popular (and useful). I certainly couldn't
live without it. And even that aside, I'd much rather have the type
system infer a most particular instance than to have to specify that
myself.

Also IMHO, adding a new construct (type (in)equality) to the language
is a lot more obtrusive than to do something meaningful of the
constructs that the language already provides. So I'd have issues with
conservative as well...

Of course, this is all from the perspective of a user, not a type
inference engine implementor... ;-)

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