Re: Keep the present Haskell record system!

2006-03-07 Thread Johannes Waldmann
Cale Gibbard wrote: (a thoughtful response, thank you) and ...

 ... field labels can be renamed such that they don't overlap.
 Inventing new names is not hard work. 

Oh yes it is. I want meaningful names, and if the meaning of two things
is identical, then inventing separate names is hard and unnecessary
and misleading.

 (You can just put part or all of the type name in the labels, 

Ugly ugly ugly. By writing fooBar (for the foo of Bar)
I'm putting type or module information in a name.
That's a bad idea because it bypasses the type or module system.


I think I really want a separate component namespace per type,
and I can only get this by putting each type in its own module,
but then another problem comes up: how to name the module/the type?

You see this in e. g. Data.Map: it contains the type Map, and says
http://www.haskell.org/ghc/docs/latest/html/libraries/base/Data-Map.html

 This module is intended to be imported qualified, to avoid name
 clashes with Prelude functions. eg.  import Data.Map as Map

but then what is the type of a map? It's Data.Map.Map (or, as the
documentation suggests, Map.Map, which does not look any better).

Sometimes my conclusion is module Foo where data Type = Make { ... }
because then import qualified Foo ; x :: Foo.Type = Foo.Make ...
(in case I'll publish the constructor). You see I want to avoid
inventing a name for the type and its constructor (if there is only one)
because I already have done it (it's the module name).

So .. what if we just allow to write a data (or class?) declaration
directly (instead of a module declaration). E. g. the file Foo.hs
contains data Foo where (... constructors as in GADT ...) ;
some_function :: ... with the effect that after import qualified Foo
from elsewhere we can write x :: Foo; .. Foo.some_function ...
Just an idea.


PS: GADTs are way cool! Any chance of having them in Haskell-Prime?
-- 
-- 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: partial type signatures/annotations/declarations..

2006-03-07 Thread Martin Sulzmann

FYI, Chameleon supports a combination of lexically scoped
and partial type annotation. The latest Chameleon version
is a broken (fix on its way). Though, besides the implementation
there's also a concise formal description. See
[July 2005] Lexically Scoped Type Annotations
http://www.comp.nus.edu.sg/~sulzmann/lexical-annot.ps

Martin

Claus Reinke writes:
  instead of introducing holes in types and contexts to leave
  parts of a declaration unspecified, why not use type subsumption?
  
  it has been pointed out to me that I should be more specific about 
  what I mean with this suggestion (not least to ensure that I don't
  suggest to use subsumption the wrong way round, thanks!-):
  
  - first, subsumption: 
  
  (P = t) subsumes (Q = r) 
  iff 
  exists substitution th. (r = th(t)  th(P) |- Q)
  
  [where |- is entailment between sets of predicates]
   
  in words: a qualified type qt1 is subsumed by a qualified type qt2
  (we write: qt1 = qt2) precisely if qt1 is a substitution instance of 
  qt2 whose constraints are implied by the substition instance of qt2's 
  constraints.
  
  - next, its use for partial type declarations:
  
  a qualified type is subsumed if its type part is more specific, and its
  constraint part is implied. so we could declare a qualified type for an 
  expression that, instead of being the precise type of said expression,
  only has to be subsumed by the inferred expression type:
  
  we write (expr :: qt_partial) iff: (expr :: qt) and (qt_partial = qt).
  
  that means that the precise type can be more specific (variables
  instantiated), have more constraints (as long as the ones given are
  implied) and even different constraints (eg., of subclasses, or of
  other constraints that imply the ones given). this accounts for uses
  of placeholders (_) in both types and constraints in the alternative
  option.
  
  note that, currently, declarations can already be more specific than 
  the inferred type:
  
  f :: Int - Int - Int
  f x y = x+y
  
  partial type declarations would permit us to declare types that are
  more general than the inferred type, allowing us to omit type info
  that we want to leave inferred (or specifying part of a type without
  having to specify all of it):
  
  f :: Int - a - Int
  or
  f :: Int - a
  or
  f :: Fractional a = a - a - a
  
  pro: would easily allow for omission of type details or parts
  of context (a type with more context, or with more specific
  type components, is subsumed by the declaration)
   
  cons: while this accounts for the explicit parts of the alternative
  option (_), that option implicitly assumes that other type
  variables cannot be instantiated, and that contexts without
  _ cannot be extended.
  
  as long as we only specify an one-sided bound, the inferred
  type could be more specific than we'd like (we can't say
  that we don't want context, or that some type variable
  must not be instantiated)
  
  hope I got it the right way round this time?
  claus
  
  ps. I can't find the original thread, but this came up again last
   year, and Oleg suggested, that for the special case of function
  signatures, the same effect could be had by adding extra fake
  clauses (similar to fake clauses commonly used for trace or seq):
  
  http://haskell.org/pipermail/haskell-cafe/2004-August/006606.html
  
  this does not work for other places where type declarations
  are required, but would be awkward or impossible to give in
  full, but at least for functions, Oleg's fake clauses might be a 
  possible desugaring (unless our clever optimising compiler
  removes them as dead code;-):
  
  -- f' :: Int - a - Int
  -- f' :: Int - a
  -- f' :: Fractional a = a - a - a
  f' :: Eq a = c - b - a
  f' = undefined
  
  f x y | False = f' x y
  f x y = x+y
  
  ___
  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


partial application syntax

2006-03-07 Thread Wolfgang Jeltsch
Hello,

there was some proposal for introducing a special syntax where f x _ z or
f x ? z means \y - f x y z.  Is there some information on the Haskell' trac 
site about this?

Best wishes,
Wolfgang
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: relaxed instance rules spec (was: the MPTC Dilemma (please solve))

2006-03-07 Thread Ben Rudiak-Gould

John Meacham wrote:

On Thu, Mar 02, 2006 at 03:53:45AM -, Claus Reinke wrote:

the problem is that we have somehow conjured up an infinite
type for Mul to recurse on without end! Normally, such infinite
types are ruled out by occurs-checks (unless you are working
with Prolog III;-), so someone forgot to do that here. why?
where? how?


Polymorphic recursion allows the construction of infinite types if I
understand what you mean.


No, that's different. An infinite type can't be written in (legal) Haskell. 
It's something like


type T = [T]

-- Ben

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