GHC.Unicode

2006-01-17 Thread Krasimir Angelov
Hello Guys,

I saw that GHC already has complete support for Unicode character
classification. I tend to use it but I saw that currently GHC.Unicode
exports only few of all classification routines. Is it intentional?

Cheers,
  Krasimir
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GHC.Unicode

2006-01-17 Thread Ross Paterson
On Tue, Jan 17, 2006 at 10:33:51AM +0200, Krasimir Angelov wrote:
 I saw that GHC already has complete support for Unicode character
 classification. I tend to use it but I saw that currently GHC.Unicode
 exports only few of all classification routines. Is it intentional?

It exports some functions used by Data.Char.  You'd be better off using
the Data.Char interface, which is also supported by Hugs, and provides
classification using Unicode general categories.  Much more could be
added, though.

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GHC.Unicode

2006-01-17 Thread Krasimir Angelov
The problem is that I have to use 'generalCategory' function which
isn't exported. It returns the general category which tells me a lot
more about the character.

2006/1/17, Ross Paterson [EMAIL PROTECTED]:
 On Tue, Jan 17, 2006 at 10:33:51AM +0200, Krasimir Angelov wrote:
  I saw that GHC already has complete support for Unicode character
  classification. I tend to use it but I saw that currently GHC.Unicode
  exports only few of all classification routines. Is it intentional?

 It exports some functions used by Data.Char.  You'd be better off using
 the Data.Char interface, which is also supported by Hugs, and provides
 classification using Unicode general categories.  Much more could be
 added, though.

 ___
 Glasgow-haskell-users mailing list
 Glasgow-haskell-users@haskell.org
 http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GHC.Unicode

2006-01-17 Thread Ross Paterson
On Tue, Jan 17, 2006 at 11:29:42AM +0200, Krasimir Angelov wrote:
 The problem is that I have to use 'generalCategory' function which
 isn't exported. It returns the general category which tells me a lot
 more about the character.

But Data.Char does export generalCategory.

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GHC.Unicode

2006-01-17 Thread Krasimir Angelov
Oh, Sorry! I didn't see it at first sight and I immediately went to
GHC.Unicode. In this case is the GHC.Unicode module still in use?

2006/1/17, Ross Paterson [EMAIL PROTECTED]:
 On Tue, Jan 17, 2006 at 11:29:42AM +0200, Krasimir Angelov wrote:
  The problem is that I have to use 'generalCategory' function which
  isn't exported. It returns the general category which tells me a lot
  more about the character.

 But Data.Char does export generalCategory.

 ___
 Glasgow-haskell-users mailing list
 Glasgow-haskell-users@haskell.org
 http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GHC.Unicode

2006-01-17 Thread Ross Paterson
On Tue, Jan 17, 2006 at 11:44:00AM +0200, Krasimir Angelov wrote:
 Oh, Sorry! I didn't see it at first sight and I immediately went to
 GHC.Unicode. In this case is the GHC.Unicode module still in use?

It's an internal module, like most GHC.* modules (except GHC.Exts).

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: cvs commit: fptools/libraries/base/Data IntMap.hs Map.hs Sequence.hs Set.hs fptools/libraries/base/Data/Generics Instances.hs Twins.hs

2006-01-17 Thread Simon Peyton-Jones
|Eta-expand some higher-rank functions.  GHC is about to
|move to *invariant* rather than *contra-variant* in function
|arguments, so far as type subsumption is concerned. These
|eta-expansions are simple, and allow type inference to
|go through with invariance.
| 
| Why drop contra-variace?

See the paper on Boxy type inference on my home page.

Simon
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Lexically scoped type variables

2006-01-17 Thread Simon Peyton-Jones
Dear GHC users

As part of a revision of GHC to make type inference for GADTs simpler
and more uniform, I propose to change the way in which lexically-
scoped type variables work in GHC.  (Indeed, I have done so, and will
commit it shortly.)  This message explains the new system, highlighting
the differences.

I'm very interested to know whether you like it or hate it.
In the latter case, I'd also like to know whether you also 
have programs that will be broken by the change.

Simon

Scoped type variables in GHC

January 2006

0) Terminology.
   
   A *pattern binding* is of the form
pat = rhs

   A *function binding* is of the form
f pat1 .. patn = rhs

   A binding of the formm
var = rhs
   is treated as a (degenerate) *function binding*.


   A *declaration type signature* is a separate type signature for a
   let-bound or where-bound variable:
f :: Int - Int

   A *pattern type signature* is a signature in a pattern: 
\(x::a) - x
f (x::a) = x

   A *result type signature* is a signature on the result of a
   function definition:
f :: forall a. [a] - a
head (x:xs) :: a = x

   The form
x :: a = rhs
   is treated as a (degnerate) function binding with a result
   type signature, not as a pattern binding.

1) The main invariants:

 A) A lexically-scoped type variable always names a rigid
type variable (not a wobbly one, and not a non-type-variable 
type).  THIS IS A CHANGE.  Previously, a scoped type variable
named an arbitrary *type*.

 B) A type signature always describes a rigid type (since
its free (scoped) type variables name rigid type variables).
This is also a change, a consequence of (A).

 C) Distinct lexically-scoped type variables name distinct
rigid type variables.  This choice is open; 

  This means that you cannot say
\(x:: [a]) - expr
  (where 'a' is not yet in scope) to enforce that x is a list without 
  saying anything about 'a'.  (Well, not unless the type of this lambda
  is known from the outside.)

1a) Possible extension.  We might consider allowing
\(x :: [ _ ]) - expr
where _ is a wild card, to mean x has type list of something,
without
naming the something.

  
2) Scoping

2(a) If a declaration type signature has an explicit forall, those type
   variables are brought into scope in the right hand side of the 
   corresponding binding (plus, for function bindings, the patterns on
   the LHS).  
f :: forall a. a - [a]
f (x::a) = [x :: a, x]
   Both occurences of 'a' in the second line are bound by 
   the 'forall a' in the first line

   A declaration type signature *without* an explicit top-level forall
   is implicitly quantified over all the type variables that are
   mentioned in the type but not already in scope.  GHC's current
   rule is that this implicit quantification does *not* bring into scope
   any new scoped type variables.
f :: a - a
f x = ...('a' is not in scope here)...
   This gives compatibility with Haskell 98

2(b) A pattern type signature implicitly brings into scope any type
   variables mentioned in the type that are not already into scope.
   These are called *pattern-bound type variables*.
g :: a - a - [a]
g (x::a) (y::a) = [y :: a, x]
   The pattern type signature (x::a) brings 'a' into scope.
   The 'a' in the pattern (y::a) is bound, as is the occurrence on 
   the RHS.  

   A pattern type siganture is the only way you can bring existentials 
   into scope.
data T where
  MkT :: forall a. a - (a-Int) - T

f x = case x of
MkT (x::a) f - f (x::a)

2a) QUESTION
class C a where
  op :: forall b. b-a-a

instance C (T p q) where
  op = rhs
Clearly p,q are in scope in rhs, but is 'b'?  Not at the moment.
Nor can you add a type signature for op in the instance decl.
You'd have to say this:
instance C (T p q) where
  op = let op' :: forall b. ...
   op' = rhs
   in op'

3) A pattern-bound type variable is allowed only if the pattern's
   expected type is rigid.  Otherwise we don't know exactly *which*
   skolem the scoped type variable should be bound to, and that means
   we can't do GADT refinement.  This is invariant (A), and it is a
change
   from the current situation.

f (x::a) = x-- NO

g1 :: b - b
g1 (x::b) = x   -- YES, because the pattern type is rigid

g2 :: b - b
g2 (x::c) = x   -- YES, same reason

h :: forall b. b - b
h (x::b) = x-- YES, but the inner b is bound

k :: forall b. b - b
k (x::c) = x-- NO, it can't be both b and c

3a) You *can* give a different name to the same type variable in
different
disjoint scopes, just as you can (if you want) give diferent names
to 
the same value 

Re: Lexically scoped type variables

2006-01-17 Thread Johannes Waldmann
On the syntax of type signatures: I'd like to be able to write e. g.

do
x :: Int - randomRIO ( 0, 10 )
print x

Currently I have to put ( x :: Int ) in parentheses. Is this necessary?
-- 
-- Johannes Waldmann -- Tel/Fax (0341) 3076 6479/80 --
 http://www.imn.htwk-leipzig.de/~waldmann/ ---

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: darcs switchover

2006-01-17 Thread Malcolm Wallace
 John Goerzen wrote:
  * I will re-convert all of the top-level directories in the current
libraries darcs repo, except for: doc, mk, and Cabal
  * Each new repo will be under darcs.haskell.org/packages

Inspired by the new browsable interface to the libraries repo at
http://darcs.haskell.org/darcsweb/
I have installed a similar darcsweb interface for the software
currently distributed through darcs at York:
http://www.cs.york.ac.uk/fp/darcs/
including cpphs, hoogle, yhc, Blobs and so on.

Meanwhile, I noted that the HaXml repo on darcs.haskell.org seems
to be a verbatim copy of the darcs repo at York.  This this right?
I was slightly disappointed, since I think I made a bit of a mess of
the CVS - darcs conversion of HaXml, and was secretly hoping that when
the fptools conversion happened, it would make a cleaner job of it,
based on the full CVS history...  Just wondering?

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Linking with C++ produced by Visual Studio .NET on Windows XP?

2006-01-17 Thread Brian Hulley

Hi -
I'm wondering if anyone has a simple Visual Studio .NET C++ project that 
would demonstrate how to link C++ with Haskell (or vice versa). Ie a .sln, 
.vcproj, .cpp, and .h file containing one C++ function and a Haskell file 
main.hs that calls this function, so that if I click on the .sln file and 
hit F6 the VS project will build then on the command line if I type 
ghc --make main.hs the Haskell program will be built so that when I type 
main on the command line it will run and call the C++ function.


Sorry if this all sounds too basic but I don't know how to compile C++ from 
the command line at all or how to use make files, and I need to use the 
Visual Studio compiler because my own C++ code relies on Microsoft 
extensions...


Thanks,

Brian. 


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: darcs switchover

2006-01-17 Thread John Goerzen
On 2006-01-17, Malcolm Wallace [EMAIL PROTECTED] wrote:
 Meanwhile, I noted that the HaXml repo on darcs.haskell.org seems
 to be a verbatim copy of the darcs repo at York.  This this right?
 I was slightly disappointed, since I think I made a bit of a mess of
 the CVS - darcs conversion of HaXml, and was secretly hoping that when
 the fptools conversion happened, it would make a cleaner job of it,
 based on the full CVS history...  Just wondering?

Ahh.  You are correct.  I noticed that you had a HaXml repository, and
believed that the copy in fptools was actually a converted-to-CVS
version of that.  In any case, I thought it would be unwise to have a
darcs repo without common history with the upstream darcs repo, so
indeed HaXml is just the fruit of darcs get from yours.

Re-converting now, since you've presumably committed patches to the
darcs side, is probably not going to be practical.

-- John


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users