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

2006-02-10 Thread isaac jones
On Thu, 2006-02-02 at 09:29 +0100, Johannes Waldmann 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.

The ticket for Johannes's proposal is here:
http://hackage.haskell.org/trac/haskell-prime/ticket/88

This looks to me like it's related to "specifying language extensions"
here:
http://www.haskell.org//pipermail/haskell-prime/2006-February/000335.html

Patryk, have you created a ticket for your proposal?  Could it be
implemented w/ annotations as described by Johannes?  Could the two of
you put together a specific proposal?

I've put a meta-proposal here for this question:
http://hackage.haskell.org/trac/haskell-prime/ticket/91

peace,

  isaac


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


the MPTC Dilemma (please solve)

2006-02-10 Thread isaac jones
I've created a wiki page and a ticket to record solutions to what I'm
calling the "Multi Parameter Type Class Dilemma".  It's summarized
thusly:

MultiParamTypeClasses are very useful, but mostly in the context of
FunctionalDependencies. They are particularly used in the monad
transformer library found in fptools. The dilemma is that functional
dependencies are "very, very tricky" (spj). AssociatedTypes are
promising but unproven. Without a solution, Haskell' will be somewhat
obsolete before it gets off the ground.

I've proposed a few solutions.  Please help to discover more solutions
and/or put them on the ticket/wiki.  

Wiki page:
http://hackage.haskell.org/trac/haskell-prime/ticket/90

Ticket:
http://hackage.haskell.org/trac/haskell-prime/wiki/MultiParamTypeClassesDilemma


peace,

  isaac



-- 
isaac jones <[EMAIL PROTECTED]>

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


Re: First class labels

2006-02-10 Thread Claus Reinke

| the concrete proposal is to address one of these remaining issues,
| namely how to identify record field labels as such. for that, I
| outlined three options, although that outline perhaps wasn't concrete 
| enough:
| 
| 1. make label declarations unneccessary (eg., #pointX :: #PointX)


effect on the type system: a new (meta-)rule for a new kind of 
literal constants: whenever we see something looking like 
" '#' ", its type is " '#'".


Essentially the same as for other literals: whenever we see
something looking like " [0-9]+ ", its type is " Num a => a ". 
whenever we see " True ", its type is " Bool ", etc. .


Similar to numeric literals, there'd be no place in source where
all those literals/labels are declared, but literals of the same type 
in different modules would be compatible. So this would work

without problems:

   module A
   main = #pointX

   module B
   main = #pointX

   module C
   import A
   import B
   main = print [A.main,B.main]

| 2. make type sharing expressible (something like the sharing
| constraints in Standard ML's module language, to allow you to
| say when two declarations from different imports refer to the
| same type)

this is definitely a type system issue. if we have

   module A where 
   data PointX = PointX deriving Show

   main = print PointX

   module B where 
   data PointX = PointX deriving Show

   main = print PointX

   module C -- this doesn't work!
   import A
   import B
   main = print PointX -- conflict here! ambiguous occurrence..

we have a problem. in a simple form, the sharing constraints I 
had in mind would permit us to express which structurally equivalent 
declarations define *the same type*. that is, module C would be


   module C
   import A
   import B
   sharing A.PointX B.PointX
   main = print PointX 
   -- no conflict, A.PointX and B.PointX have been 
   -- identified, refer to the same type


the type system would need to unify the shared types. to make 
that safe, it would need to check for structural equivalence of the
declarations when encountering a sharing constraint; if successful, 
both shared types would afterwards be seen as synonyms for 
one and the same type.


A very minimal version of this option would suffice for labels;

in general, this kind of sharing constraints is non-trivial, but useful
(if we could share classes and instances defined multiple times,
like the instances for (,,,) discussed in other threads).

| 3. introduce a least upper bound for shared label imports
| (so A and B could just 'import Data.Label(pointX)', which
|  would magically provide the shared declaration for pointX)

with this option, the modules would look like this

   module A
   import Data.Label(pointX)

   module B
   import Data.Label(pointX)
   
   module C

   import A
   import B
   main = print pointX 
   -- no conflict, A.pointX and B.pointX are the same


this would have a similarly small effect on the type system as option 1,
only that instead of syntax, we'd use imports from the reserved module
'Data.Label' to identify what is a label and what is not.

whenever encountering an ' import Data.Label() ', we
interpret ' Data.Label. ' as a constant of type 
' Data.Label. ' and '  ' as a constant of

type '  '. the difference to normal imports is that the
compiler/type system needs to know about 'Data.Label'.

In other words, 'Data.Label' does not exist in source or object code,
but as a hint for the compiler/type system. Any identifier imported from
there is a label of its own type, nothing else can be imported from there.

sorry for being so difficult to understand. the questions help.

cheers,
claus

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


RE: First class labels

2006-02-10 Thread Simon Peyton-Jones
| the concrete proposal is to address one of these remaining issues,
| namely how to identify record field labels as such. for that, I
outlined
| three options, although that outline perhaps wasn't concrete enough:
| 
| 1. make label declarations unneccessary (eg., #pointX :: #PointX)
| 
| 2. make type sharing expressible (something like the sharing
| constraints in Standard ML's module language, to allow you to
| say when two declarations from different imports refer to the
| same type)
| 
| 3. introduce a least upper bound for shared label imports
| (so A and B could just 'import Data.Label(pointX)', which
|  would magically provide the shared declaration for pointX)

Thanks for the clarifications.  But I am still in the dark.  I have
literally no clue about *exactly* what your suggestions would entail.
What would the effect on the type system of (1) be?  Or (2) -- is it
just a name-space issue or is it something to do with types.  Or (3) --
I have even less clue here. Sorry to be dense

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


Re: First class labels

2006-02-10 Thread Claus Reinke

Simon

thanks for the questions. I'll try to clarify.

[1]

...   For example, what does it mean to "remove the need to
declare labels, make them identifiable as such in use"? 


implicit label declarations, basically.

the code for records I posted depends on any two field labels being 
distinguishable by type. to get readable records, we want something

like typed constants, e.g.:

   data LabelX = LabelX deriving (..)

but all these declarations will be the same, apart from the label name,
so if we had syntactic means to see that something is a label, and the
only inhabitant of its type, there'd be no need for these declarations. 

for the sake of discussion, let us assume that we reserve a '#' prefix 
before identifiers and types to single them out as label-related. 
then we'd know (without explicit declaration) that


   #labelX :: #LabelX

why would that be interesting? that brings us to your second issue:

[2]
Then, the code that you enclosed appeared to show that you could 
do without any extension at all.


the code establishes a context for the proposal, nothing more.

the code demonstrates that there are record system variants that we
can implement without any new language extensions. but it could not
be used in practical, multi-module situations, because of the need to 
declare those label types.


if we have two modules, A and B (think ...OpenGL and some GUI
library), that both want to use records with fields named 'pointX', 
they'd both have to declare the field label as


data PointX = PointX deriving (..)

now, if we ever want to import A and B into the same module C
(think OpenGL windows in a GUI), we are in trouble, because we 
have two "conflicting" declarations for PointX. at the moment, that 
means that we have two ways out


   - either use qualified names in C: A.PointX and B.PointX;
   this is awkward, to say the least, and still doesn't let us
   identify what should be two instances of the same field 
   name, forcing upon us superfluous conversions


   - or modify the imports: introduce a new module PointX that
  declares PointX, and have both A and B import that;
   this is impractical: it breaks module composition, and there
   is no least upper bound in the import hierarchy where we
   can safely place our label declarations once and for all

which brings us to your final suggestion:
  
[3]

Records are a huge swamp with a very large number of possible variants
and design choices.  Perhaps you might gain more traction if you were
ruthlessly specific about what language changes you advocate, and what
benefits they would have (versus the existing situation).


I was trying to single out a minimal extension that might help to steer
around that swamp (which seems to be the undeclared intention for
Haskell'?), while still providing the means for making progress wrt 
a better record system for Haskell'. I was explicitly _not_ suggesting

to build any new record system variant into the language.

the code shows by example what is possible without new extensions
while also highlighting issues that are not easily addressed without new
extensions (and making old extensions official parts of the language). 


the concrete proposal is to address one of these remaining issues,
namely how to identify record field labels as such. for that, I outlined
three options, although that outline perhaps wasn't concrete enough:

1. make label declarations unneccessary (eg., #pointX :: #PointX)

2. make type sharing expressible (something like the sharing 
   constraints in Standard ML's module language, to allow you to 
   say when two declarations from different imports refer to the 
   same type)


3. introduce a least upper bound for shared label imports
   (so A and B could just 'import Data.Label(pointX)', which
would magically provide the shared declaration for pointX)

does that clear things up a bit? if anyone still has questions, 
please ask!-)


cheers,
claus

original message:
http://www.haskell.org//pipermail/haskell-prime/2006-February/000463.html

   
___

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


Re: Scoped type variables

2006-02-10 Thread Ross Paterson
On Wed, Feb 08, 2006 at 05:48:24PM -, Simon Peyton-Jones wrote:
> | >b) A pattern type signature may bring into scope a skolem bound
> | >   in the same pattern:
> | >   data T where
> | > MkT :: a -> (a->Int) -> T
> | >   f (MkT (x::a) f) = ...
> | >
> | >   The skolem bound by MkT can be bound *only* in the patterns that
> | >   are the arguments to MkT (i.e. pretty much right away).
> [...]
>   f (MkT (x::a) (f::a->Int)) = ...
> 
> You can imagine that either (a) both bind 'a' to the skolem, but must do
> consistently; or (b) that (x::a) binds 'a', and (f::a->Int) is a bound
> occurrence.  It doesn't matter which you choose, I think.

Another possibility would be to allow an optional explicit quantifier
before the data constructor, mirroring the old datatype syntax for
existentials:

data T = forall a. MkT a (a->Int)

f (forall a. MkT x f) = ...

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


Re: runtime reflection for classes

2006-02-10 Thread Johannes Waldmann
Donald Bruce Stewart wrote:

> Depending on how evil you are, you can already do this. Call the show,
> and if it doesn't exist you can catch the exception that is thrown 

Brilliant. By the way, this idea also solves the problem
of not being able to define defaults for record fields, like so:

import Control.Exception

data Thing = Thing { foo :: Int, bar :: Int } deriving Show

wrap :: Thing -> IO Thing
wrap x =
( foo x `seq` bar x `seq` return x )
`Control.Exception.catch` \ _ ->
( foo x `seq` return $ x { bar = 2 } )
`Control.Exception.catch` \ _ ->
( bar x `seq` return $ x { foo = 4 } )
`Control.Exception.catch` \ _ ->
return $ Thing { foo = 4, bar = 2 }

main = do
wrap ( Thing { foo = 5 } ) >>= print
wrap ( Thing { bar = 7 } ) >>= print
wrap ( Thing { } ) >>= print
-- 
-- 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: First class labels

2006-02-10 Thread Simon Peyton-Jones
| To make up for this, I've now extended the example code to
| include more operations, cryptic infix operators, and more
| type class tricks (we have examples of record field selection,
| symmetric record concatenation, record field removal, record
| field update, record field renaming).

Claus

I did read your message.  I'm afraid I couldn't figure out exactly what
you were proposing, so I filed it hoping that the ensuing discussion
would clarify.   For example, what does it mean to "remove the need to
declare labels, make them identifiable as such in use"?  I had similar
questions about your other two options.

Then, the code that you enclosed appeared to show that you could do
without any extension at all.

Records are a huge swamp with a very large number of possible variants
and design choices.  Perhaps you might gain more traction if you were
ruthlessly specific about what language changes you advocate, and what
benefits they would have (versus the existing situation).

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


Fwd: [Haskell] context rules for "default"

2006-02-10 Thread Bulat Ziganshin

it seems like a good question for committee ;)

This is a forwarded message
From: Doug McIlroy <[EMAIL PROTECTED]>
To: haskell@haskell.org
Date: Thursday, February 09, 2006, 11:17:36 PM
Subject: [Haskell] context rules for "default"

===8<==Original message text===
What is the rationale for the requirement that, in order for
the ambiguous type of a numeric constant to be resolved by the
default declaration, all classes in the context must be in the
Standard Prelude or Standard Library (Revised Report 4.3.4)?
This makes it hard to introduce new polymorphic functions
whose domain includes the integers.

Doug McIlroy
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell

===8<===End of original message text===



-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



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