RE: ANNOUNCE: GHC 7.4.1 Release Candidate 1

2011-12-23 Thread Simon Peyton-Jones
Yes, it's expected; it's also the behaviour of GHC 6.12 etc.

Here what is happening.  You define
result = undefined
What type does it get?  In 6.12, and 7.4, it gets type
result :: forall b. b
So the two uses of 'result' in the two branches of the case have no effect on 
each other.

But in 7.2 it was *not generalised*, so we got
result :: f2 a
And now the two uses *do* affect each other.


Why the change. You'll remember that over the last year GHC has changed not to 
generalise local lets: 
http://hackage.haskell.org/trac/ghc/blog/LetGeneralisationInGhc7

I relaxed the rule in 7.2, as discussed in Which bindings are affected? in 
that post. For reasons I have not investigated, 7.2 *still* doesn't generalise 
'result'; but 7.4 correctly does.

Simon

| -Original Message-
| From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-
| users-boun...@haskell.org] On Behalf Of Antoine Latter
| Sent: 23 December 2011 04:21
| To: glasgow-haskell-users@haskell.org
| Subject: Re: ANNOUNCE: GHC 7.4.1 Release Candidate 1
| 
| On Wed, Dec 21, 2011 at 1:29 PM, Ian Lynagh ig...@earth.li wrote:
| 
|  We are pleased to announce the first release candidate for GHC 7.4.1:
| 
|     http://www.haskell.org/ghc/dist/7.4.1-rc1/
| 
|  This includes the source tarball, installers for OS X and Windows, and
|  bindists for amd64/Linux, i386/Linux, amd64/FreeBSD and i386/FreeBSD.
| 
|  Please test as much as possible; bugs are much cheaper if we find them
|  before the release!
| 
| 
| Hurrah!
| 
| The following used to compile with GHC 7.2.1:
| 
| 
| {-# LANGUAGE RankNTypes, TypeFamilies, GADTs #-}
| 
| import Data.Typeable ( Typeable1, gcast1, typeOf1 )
| 
| cast1 :: (Typeable1 f1, Typeable1 f2) = f1 a - f2 a
| cast1 val
|   = case gcast1 (Just val) of
|   Just (Just typed_val) - typed_val `asTypeOf` result
|   Nothing - error $ Invalid cast:  ++ tag ++  -  ++ show
| (typeOf1 result)
|   where result = undefined
| tag = show (typeOf1 val)
| 
| main = putStrLn Hello, world!
| 
| 
| But with GHC 7.4.1 RC 1 I get the error:
| 
| 
| BugDowncast.hs:9:69:
| Ambiguous type variable `t0' in the constraint:
|   (Typeable1 t0) arising from a use of `typeOf1'
| Probable fix: add a type signature that fixes these type variable(s)
| In the first argument of `show', namely `(typeOf1 result)'
| In the second argument of `(++)', namely `show (typeOf1 result)'
| In the second argument of `(++)', namely
|   ` -  ++ show (typeOf1 result)'
| 
| 
| Is this an expected change, or should I create a ticket?
| 
| Thanks,
| Antoine
| 
| 
|  The release notes are not yet available, but here are some of the
|  highlights of the 7.4 branch since 7.2 and 7.0:
| 
|   * There is a new feature Safe Haskell (-XSafe, -XTrustworthy, -XUnsafe):
|       http://www.haskell.org/ghc/dist/stable/docs/html/users_guide/safe-
| haskell.html
|     The design has changed since 7.2.
| 
|   * There is a new feature kind polymorphism (-XPolyKinds):
|       http://www.haskell.org/ghc/dist/stable/docs/html/users_guide/kind-
| polymorphism-and-promotion.html
|     A side-effect of this is that, when the extension is not enabled, in
|     certain circumstances kinds are now defaulted to * rather than being
|     inferred.
| 
|   * There is a new feature constraint kinds (-XConstraintKinds):
| 
|  http://www.haskell.org/ghc/dist/stable/docs/html/users_guide/constraint-
| kind.html
| 
|   * It is now possible to give any sort of declaration at the ghci prompt:
| 
|  http://www.haskell.org/ghc/dist/stable/docs/html/users_guide/interactive-
| evaluation.html#ghci-decls
|     For example, you can now declare datatypes within ghci.
| 
|   * The profiling and hpc implementations have been merged and overhauled.
|     Visible changes include renaming of profiling flags:
|       http://www.haskell.org/ghc/dist/stable/docs/html/users_guide/flag-
| reference.html#id589412
|     and the cost-centre stacks have a new semantics, which should in most
|     cases result in more useful and intuitive profiles. The +RTS -xc flag
|     now also gives a stack trace.
| 
|   * It is now possible to write compiler plugins:
|       http://www.haskell.org/ghc/dist/stable/docs/html/users_guide/compiler-
| plugins.html
| 
|   * DPH support has been significantly improved.
| 
|   * There is now preliminary support for registerised compilation using
|     LLVM on the ARM platform.
| 
| 
|  Note: The release candidate accidentally includes the random, primitive,
|  vector and dph libraries. The final release will not include them.
| 
| 
|  Thanks
|  Ian, on behalf of the GHC team
| 
| 
|  ___
|  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
| 

RE: ConstraintKinds and default associated empty constraints

2011-12-23 Thread Simon Peyton-Jones
it’s a bug.  I’m fixing it.

Simon

From: glasgow-haskell-users-boun...@haskell.org 
[mailto:glasgow-haskell-users-boun...@haskell.org] On Behalf Of Edward Kmett
Sent: 22 December 2011 17:03
To: Bas van Dijk
Cc: glasgow-haskell-users@haskell.org
Subject: Re: ConstraintKinds and default associated empty constraints

On Wed, Dec 21, 2011 at 6:45 PM, Bas van Dijk 
v.dijk@gmail.commailto:v.dijk@gmail.com wrote:
I'm playing a bit with the new ConstraintKinds feature in GHC
7.4.1-rc1. I'm trying to give the Functor class an associated
constraint so that we can make Set an instance of Functor. The
following code works but I wonder if the trick with: class Empty a;
instance Empty a, is the recommended way to do this:

{-# LANGUAGE ConstraintKinds, TypeFamilies, FlexibleInstances #-}

import GHC.Prim (Constraint)

import Prelude hiding (Functor, fmap)

import   Data.Set (Set)
import qualified Data.Set as S (map, fromList)

class Functor f where
type C f :: * - Constraint
type C f = Empty

fmap :: (C f a, C f b) = (a - b) - f a - f b

class Empty a; instance Empty a

instance Functor Set where
type C Set = Ord
fmap = S.map

instance Functor [] where
fmap = map

testList = fmap (+1) [1,2,3]
testSet  = fmap (+1) (S.fromList [1,2,3])

Cheers and thanks for a great new feature!

Bas

This is the same solution I wound up with in

https://github.com/ekmett/constraints

Adding an argument to the family would work but is somewhat unsatisfying as it 
mucks with polymorphic recursive use of the dictionary, and with placing 
constraints on constraints, so I prefer to keep as few arguments as possible.

You can go farther with Functor by using polymorphic kinds and indexing the 
source and destination Category as well as the class of objects in the category.

I should probably write up what I've done with this, but doing so lets you have 
real product and coproduct Category instances, which were previously not 
possible (a fact which in part drove me to write all the semigroupoid code i 
have on hackage.

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


Unit unboxed tuples

2011-12-23 Thread Simon Peyton-Jones
Dear GHC users

I've just discovered something very peculiar with unboxed tuples in GHC.

f2 x = (# True, False #)
f1 x = (# True #)
f0 x = (# #)

What types do these functions have?
f2 :: a - (# Bool, Bool #)
f1 :: a - (# Bool #)
BUT
f0 :: a - b - (# b #)

I think this is stupid.  It should be

f0 :: a - (# #)

But in fact even that type isn't what you expect (ie the analogue of  f :: a - 
() )
Here are the kinds of the type constructors:

(,,) :: * - * - * - *
(,) :: * - * - *
() :: *

(# ,, #) :: * - * - * - #
(# , #) :: *  - * - #
BUT
(#  #) :: * - #

In both respects unboxed unit tuples are behaving differently to boxed ones. 
This seems bonkers.  I propose to fix this, but I wanted to check if anyone is 
relying on the current odd behaviour.


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


Re: Unit unboxed tuples

2011-12-23 Thread Ian Lynagh
On Fri, Dec 23, 2011 at 12:46:38PM +, Simon Peyton-Jones wrote:
 Dear GHC users
 
 I've just discovered something very peculiar with unboxed tuples in GHC.

The problem is that there is no boxed singleton tuple, whereas there is
an unboxed singleton tuple, so there is a conflict between the data
constructor for singleton and unit, right?:

Arguments   Boxed  Unboxed
3   ( , , )(# , , #)
2   ( , )  (# , #)
1  (# #)
0   () (# #)


Thanks
Ian


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


RE: Unit unboxed tuples

2011-12-23 Thread Simon Peyton-Jones
Your table isn't quite right.  For data constructors the current situation is 
this:

Arguments   Boxed  Unboxed
3   ( , , )(# , , #)
2   ( , )  (# , #)
1  (# #)
0   () 

Wierd!  Indeed, in my proposal, here is no singleton data constructor for boxed 
tuples either! 

Arguments   Boxed  Unboxed
3   ( , , )(# , , #)
2   ( , )  (# , #)
1   
0   () (# #)

More uniform!  If you the singleton-unboxed-tuple data constructor in source 
code, as a function, you'd write (\x - (# x #)).   In a pattern, or applied, 
you'd write (# x #).

So then we have (for data constructors):

Arguments   Boxed  Unboxed
3   ( , , )(# , , #)
2   ( , )  (# , #)
1   
0   () (# #)

Simple, uniform.

Simon

| -Original Message-
| From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-
| users-boun...@haskell.org] On Behalf Of Ian Lynagh
| Sent: 23 December 2011 13:17
| To: glasgow-haskell-users@haskell.org
| Subject: Re: Unit unboxed tuples
| 
| On Fri, Dec 23, 2011 at 12:46:38PM +, Simon Peyton-Jones wrote:
|  Dear GHC users
| 
|  I've just discovered something very peculiar with unboxed tuples in GHC.
| 
| The problem is that there is no boxed singleton tuple, whereas there is
| an unboxed singleton tuple, so there is a conflict between the data
| constructor for singleton and unit, right?:
| 
| Arguments   Boxed  Unboxed
| 3   ( , , )(# , , #)
| 2   ( , )  (# , #)
| 1  (# #)
| 0   () (# #)
| 
| 
| Thanks
| Ian
| 
| 
| ___
| 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: Unit unboxed tuples

2011-12-23 Thread Ian Lynagh
On Fri, Dec 23, 2011 at 01:34:49PM +, Simon Peyton-Jones wrote:
 
 Arguments   Boxed  Unboxed
 3   ( , , )(# , , #)
 2   ( , )  (# , #)
 1 
 0   () (# #)
 
 Simple, uniform.

Uniform horizontally, but strange vertically!

Anyway, I don't have a better suggestion, and your proposal seems better
than the status quo.


Thanks
Ian


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


Re: ANNOUNCE: GHC 7.4.1 Release Candidate 1

2011-12-23 Thread Joachim Breitner
Hi,

Am Mittwoch, den 21.12.2011, 18:29 + schrieb Ian Lynagh:
 Please test as much as possible; bugs are much cheaper if we find them
 before the release!

the build system seems to be quite confused on arch/os-combinations
besides {i386,amd64}/linux. All these worked fine with 7.2.2:

https://buildd.debian.org/status/package.php?p=ghcsuite=experimental

ghc-stage1: panic! (the 'impossible' happened)
  (GHC version 7.4.0.20111219 for x86_64-unknown-kfreebsdgnu):
Don't know if OSUnknown is elf

ghc-stage1: panic! (the 'impossible' happened)
  (GHC version 7.4.0.20111219 for i386-unknown-kfreebsdgnu):
Don't know if OSUnknown is elf

ghc-stage2: panic! (the 'impossible' happened)
  (GHC version 7.4.0.20111219 for powerpc-unknown-linux):
Cant do annotations without GHCi
{libraries/vector/Data/Vector/Fusion/Stream/Monadic.hs:104:19-33}
base:GHC.Exts.ForceSpecConstr{d rbL}

ghc-stage1: panic! (the 'impossible' happened)
  (GHC version 7.4.0.20111219 for s390-ibm-linux):
Don't know if ArchUnknown is 32bit

ghc-stage1: panic! (the 'impossible' happened)
  (GHC version 7.4.0.20111219 for s390x-ibm-linux):
Don't know if ArchUnknown is 32bit

ghc-stage1: panic! (the 'impossible' happened)
  (GHC version 7.4.0.20111219 for sparc-unknown-linux):
pprGlobalReg: Unsupported register: CCCS

Do you think you can fix these for the next release release candidate?

About the powerpc problem: GHCi has been broken on powerpc for quite
some time, so we disabled it:
http://patch-tracker.debian.org/patch/series/view/ghc/7.4.0.20111219-1/no_ghci_on_powerpc
Maybe you also want to do that in your config.mk.in.

I guess the build failure above will go away with the next release
candidate, as vector was included by accident?

Greetings and thanks,
Joachim


-- 
Joachim nomeata Breitner
Debian Developer
  nome...@debian.org | ICQ# 74513189 | GPG-Keyid: 4743206C
  JID: nome...@joachim-breitner.de | http://people.debian.org/~nomeata


signature.asc
Description: This is a digitally signed message part
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: ANNOUNCE: GHC 7.4.1 Release Candidate 1

2011-12-23 Thread Antoine Latter
On Fri, Dec 23, 2011 at 3:04 AM, Simon Peyton-Jones
simo...@microsoft.com wrote:
 Yes, it's expected; it's also the behaviour of GHC 6.12 etc.

 Here what is happening.  You define
        result = undefined
 What type does it get?  In 6.12, and 7.4, it gets type
        result :: forall b. b
 So the two uses of 'result' in the two branches of the case have no effect on 
 each other.

 But in 7.2 it was *not generalised*, so we got
        result :: f2 a
 And now the two uses *do* affect each other.



Thanks for the explanation.

So the 'where' binding in the following does not get generalized
because it could not have been written at the top level, correct?


cast :: (Typeable a, Typeable b) = a - Maybe b
cast x = r
   where
 r = if typeOf x == typeOf (fromJust r)
   then Just $ unsafeCoerce x
   else Nothing


 Why the change. You'll remember that over the last year GHC has changed not 
 to generalise local lets: 
 http://hackage.haskell.org/trac/ghc/blog/LetGeneralisationInGhc7

 I relaxed the rule in 7.2, as discussed in Which bindings are affected? in 
 that post. For reasons I have not investigated, 7.2 *still* doesn't 
 generalise 'result'; but 7.4 correctly does.

 Simon

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


RE: ANNOUNCE: GHC 7.4.1 Release Candidate 1

2011-12-23 Thread Simon Peyton-Jones
| So the 'where' binding in the following does not get generalized
| because it could not have been written at the top level, correct?

The other way round.  'where' bindings that could have been written at top 
level *are* generalised; ones that could not are *not* generalised.  See Which 
bindings are affected? in 
http://hackage.haskell.org/trac/ghc/blog/LetGeneralisationInGhc7, which tries 
to be precise. If it's hard to understand can I make it easier?

Simon

| 
| 
| cast :: (Typeable a, Typeable b) = a - Maybe b
| cast x = r
|where
|  r = if typeOf x == typeOf (fromJust r)
|then Just $ unsafeCoerce x
|else Nothing
| 
| 
|  Why the change. You'll remember that over the last year GHC has changed not
| to generalise local lets:
| http://hackage.haskell.org/trac/ghc/blog/LetGeneralisationInGhc7
| 
|  I relaxed the rule in 7.2, as discussed in Which bindings are affected?
| in that post. For reasons I have not investigated, 7.2 *still* doesn't
| generalise 'result'; but 7.4 correctly does.
| 
|  Simon

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


Re: Unit unboxed tuples

2011-12-23 Thread Ganesh Sittampalam
On 23/12/2011 13:46, Ian Lynagh wrote:
 On Fri, Dec 23, 2011 at 01:34:49PM +, Simon Peyton-Jones wrote:

 Arguments   Boxed  Unboxed
 3   ( , , )(# , , #)
 2   ( , )  (# , #)
 1
 0   () (# #)

 Simple, uniform.
 
 Uniform horizontally, but strange vertically!

It's worth mentioning that if you want to write code that's generic over
tuples in some way, the absence of a case for singletons is actually a
bit annoying - you end up adding something like a One constructor to
paper over the gap. But I can't think of any nice syntax for that case
either.

Cheers,

Ganesh

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


Re: ANNOUNCE: GHC 7.4.1 Release Candidate 1

2011-12-23 Thread Felipe Almeida Lessa
On Fri, Dec 23, 2011 at 12:33 PM, Simon Peyton-Jones
simo...@microsoft.com wrote:
 | So the 'where' binding in the following does not get generalized
 | because it could not have been written at the top level, correct?

 The other way round.  'where' bindings that could have been written at top 
 level *are* generalised; ones that could not are *not* generalised.  See 
 Which bindings are affected? in 
 http://hackage.haskell.org/trac/ghc/blog/LetGeneralisationInGhc7, which tries 
 to be precise. If it's hard to understand can I make it easier?

For me it seems that both of you, gentlemen, are saying the same thing =).

Cheers,

-- 
Felipe.

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


Re: ConstraintKinds and default associated empty constraints

2011-12-23 Thread Edward Kmett
Fair enough.

So if I understand you correctly, () is becoming more overloaded as to its 
kind? 

Right now it seems it is either * or Constraint depending on context. 

As I understand you, fixing this seems to indicate that () could have any 'a - 
Constraint' kind as well.

This raises similar questions about (,) and how to build 'a - Constraint' 
products nicely.

Sent from my iPad

On Dec 23, 2011, at 4:42 AM, Simon Peyton-Jones simo...@microsoft.com wrote:

 it’s a bug.  I’m fixing it.
 
 Simon
  
 From: glasgow-haskell-users-boun...@haskell.org 
 [mailto:glasgow-haskell-users-boun...@haskell.org] On Behalf Of Edward Kmett
 Sent: 22 December 2011 17:03
 To: Bas van Dijk
 Cc: glasgow-haskell-users@haskell.org
 Subject: Re: ConstraintKinds and default associated empty constraints
  
 On Wed, Dec 21, 2011 at 6:45 PM, Bas van Dijk v.dijk@gmail.com wrote:
 I'm playing a bit with the new ConstraintKinds feature in GHC
 7.4.1-rc1. I'm trying to give the Functor class an associated
 constraint so that we can make Set an instance of Functor. The
 following code works but I wonder if the trick with: class Empty a;
 instance Empty a, is the recommended way to do this:
 
 {-# LANGUAGE ConstraintKinds, TypeFamilies, FlexibleInstances #-}
 
 import GHC.Prim (Constraint)
 
 import Prelude hiding (Functor, fmap)
 
 import   Data.Set (Set)
 import qualified Data.Set as S (map, fromList)
 
 class Functor f where
 type C f :: * - Constraint
 type C f = Empty
 
 fmap :: (C f a, C f b) = (a - b) - f a - f b
 
 class Empty a; instance Empty a
 
 instance Functor Set where
 type C Set = Ord
 fmap = S.map
 
 instance Functor [] where
 fmap = map
 
 testList = fmap (+1) [1,2,3]
 testSet  = fmap (+1) (S.fromList [1,2,3])
 
 Cheers and thanks for a great new feature!
 
 Bas
 
  
 This is the same solution I wound up with in
  
 https://github.com/ekmett/constraints 
  
 Adding an argument to the family would work but is somewhat unsatisfying as 
 it mucks with polymorphic recursive use of the dictionary, and with placing 
 constraints on constraints, so I prefer to keep as few arguments as possible.
  
 You can go farther with Functor by using polymorphic kinds and indexing the 
 source and destination Category as well as the class of objects in the 
 category.
  
 I should probably write up what I've done with this, but doing so lets you 
 have real product and coproduct Category instances, which were previously not 
 possible (a fact which in part drove me to write all the semigroupoid code i 
 have on hackage.
  
 -Edward
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: Unit unboxed tuples

2011-12-23 Thread Simon Peyton-Jones
Very hard to be generic over *unboxed* tuples! 

But yes the non-uniformity in boxed tuples is annoying.

| -Original Message-
| From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-
| users-boun...@haskell.org] On Behalf Of Ganesh Sittampalam
| Sent: 23 December 2011 14:37
| To: glasgow-haskell-users@haskell.org
| Subject: Re: Unit unboxed tuples
| 
| On 23/12/2011 13:46, Ian Lynagh wrote:
|  On Fri, Dec 23, 2011 at 01:34:49PM +, Simon Peyton-Jones wrote:
| 
|  Arguments   Boxed  Unboxed
|  3   ( , , )(# , , #)
|  2   ( , )  (# , #)
|  1
|  0   () (# #)
| 
|  Simple, uniform.
| 
|  Uniform horizontally, but strange vertically!
| 
| It's worth mentioning that if you want to write code that's generic over
| tuples in some way, the absence of a case for singletons is actually a
| bit annoying - you end up adding something like a One constructor to
| paper over the gap. But I can't think of any nice syntax for that case
| either.
| 
| Cheers,
| 
| Ganesh
| 
| ___
| 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: ConstraintKinds and default associated empty constraints

2011-12-23 Thread Edward Kmett
On Fri, Dec 23, 2011 at 10:17 AM, Simon Peyton-Jones
simo...@microsoft.comwrote:

  Right now it seems it is either * or Constraint depending on context. ***
 *

 ** **

 Correct.  Tuple bracket are used for both types and Constraints, and we
 have to decide which from context.  

 **


Whew, that agrees with my original understanding. =)

My attempt at forming a new understanding was driven by your example.

class Functor f where
type C f :: * - Constraint
type C f = ()


such that

C :: (* - *) - * - Constraint

In that, you put () in a position where it would have kind * - Constraint,
hence my confusion when you subsequently stated that there was a bug that
needed to be fixed. =)

No.  () has kind * or Constraint, depending on context, never a -
 Constraint.

 Similarly (,) has kind * - * - * or Constraint - Constraint -
 Constraint, depending on context.


**

 Imaging that there are two sorts of parens, one for types and one for
 constraints.  We figure out which is intended from context.


Yep. We have a small compiler here at ClariFi for a very Haskell-like
language in which we've implemented pretty much this same scheme.

That said, instead of magically swapping kinds out we instead take the
superkind level and introduce subtyping at that level, giving us two
superkinds, say, Box and Circle, such that Circle is a sub-superkind of Box
and both * and Constraint have superkind Circle.

Then (,) :: forall (a: Circle). a - a - a and you don't need to swap
kinds on fully saturated tuples, and it can kind check types like '(,) ()'
in isolation without issue.

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


RE: ConstraintKinds and default associated empty constraints

2011-12-23 Thread Simon Peyton-Jones
My attempt at forming a new understanding was driven by your example.

class Functor f where
   type C f :: * - Constraint
   type C f = ()

sorry -- that was simply type incorrect.  () does not have kind *  - Constraint

S

From: Edward Kmett [mailto:ekm...@gmail.com]
Sent: 23 December 2011 16:41
To: Simon Peyton-Jones
Cc: Bas van Dijk; glasgow-haskell-users@haskell.org
Subject: Re: ConstraintKinds and default associated empty constraints

On Fri, Dec 23, 2011 at 10:17 AM, Simon Peyton-Jones 
simo...@microsoft.commailto:simo...@microsoft.com wrote:
Right now it seems it is either * or Constraint depending on context.

Correct.  Tuple bracket are used for both types and Constraints, and we have to 
decide which from context.

Whew, that agrees with my original understanding. =)

My attempt at forming a new understanding was driven by your example.

class Functor f where
   type C f :: * - Constraint
   type C f = ()

such that

C :: (* - *) - * - Constraint

In that, you put () in a position where it would have kind * - Constraint, 
hence my confusion when you subsequently stated that there was a bug that 
needed to be fixed. =)

No.  () has kind * or Constraint, depending on context, never a - Constraint.
Similarly (,) has kind * - * - * or Constraint - Constraint - Constraint, 
depending on context.

Imaging that there are two sorts of parens, one for types and one for 
constraints.  We figure out which is intended from context.

Yep. We have a small compiler here at ClariFi for a very Haskell-like language 
in which we've implemented pretty much this same scheme.

That said, instead of magically swapping kinds out we instead take the 
superkind level and introduce subtyping at that level, giving us two 
superkinds, say, Box and Circle, such that Circle is a sub-superkind of Box and 
both * and Constraint have superkind Circle.

Then (,) :: forall (a: Circle). a - a - a and you don't need to swap kinds on 
fully saturated tuples, and it can kind check types like '(,) ()' in isolation 
without issue.

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


RE: Records in Haskell

2011-12-23 Thread Simon Peyton-Jones
Are Records stalled out again? I am perfectly willing to leave the fate of 
records up to a willing and capable implementer. That seems much better than 
waiting another 5 years for perfection :)

Yes, they are stalled again.  The simple solution turned out to be not 
simple.  I wrote it up at length in

http://hackage.haskell.org/trac/ghc/wiki/Records/OverloadedRecordFields
There are various unsatisfactory aspects of the proposal, particularly 
concerning record update.  I am not sure how to resolve them.

There was essentially no reaction.  As it's quite a lot of work to implement, 
and no one seemed to care very much, I put it back on the back burner.   So 
that's where it stands.

Meanwhile, AntC has put forth another proposal that I have not had time to look 
at in detail.
http://www.haskell.org/pipermail/glasgow-haskell-users/2011-December/021298.html

What this needs is someone (not me) to lead the discussion and try to make sure 
it makes progress.  For example, does AntC's proposal work? Is it better than 
the one I articulated?  Are any other variants worth considering? Is the gain 
from overloading record fields worth the pain or design and implementation?
Volunteers, stand forth!

Simon


From: Greg Weber [mailto:g...@gregweber.info]
Sent: 09 December 2011 19:38
To: Simon Peyton-Jones
Cc: Wolfgang Jeltsch; glasgow-haskell-users@haskell.org
Subject: Re: Records in Haskell

Are Records stalled out again? I am perfectly willing to leave the fate of 
records up to a willing and capable implementer. That seems much better than 
waiting another 5 years for perfection :)

As an intermediate step, is it possible to put a warning in 7.4 when the dot 
operator is used without a space so that it can be reserved for usage with a 
records solution? Or will the new records solution be turned on by an extension 
anyways?

On Mon, Nov 7, 2011 at 10:21 AM, Simon Peyton-Jones 
simo...@microsoft.commailto:simo...@microsoft.com wrote:
| would inclusion of such a record system into GHC mean that plans for
| first-class labels (http://tinyurl.com/7fppj32) are abandoned? That
| would be a pity, since first-class labels are very useful to implement
| record systems that go beyond what the abovementioned record system
| provides. See, for example, my work on records:
|  
http://www.informatik.tu-cottbus.de/~jeltsch/research/ppdp-2010-paper.pdf
|  http://hackage.haskell.org/package/records
The story is summarised at
   http://hackage.haskell.org/trac/ghc/wiki/Records

First-class labels are one point in the vast swamp of competing and overlapping 
proposals for records.  I think they are summarise here:
   http://hackage.haskell.org/trac/ghc/wiki/ExtensibleRecords
I am unsure which of this list of proposals you are referring to. The URL you 
quote is this
   http://hackage.haskell.org/trac/haskell-prime/wiki/FirstClassLabels
but it doesn't seem to actually contain a design, merely some options for a 
design that is implicit.  If you do have a design you advocate, it would be 
good to add it to the list at
   http://hackage.haskell.org/trac/ghc/wiki/ExtensibleRecords
perhaps explaining which of the other members of the list it subsumes.

Because there are so many proposals I have not gone ahead with any of them.  
The most recent thread, articulated at
   http://hackage.haskell.org/trac/ghc/wiki/Records
is to ask what is the *smallest change* that would solve the *most pressing 
problem*, namely the inability to use the same field name in different records. 
 First class labels is (I assume) much more ambitious.  But maybe not.

Anything you can do to bring clarity to the swamp, by editing the above two 
pages, would be a great service to the community.  At the moment, we are stuck 
in an infinite loop.

Simon

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.orgmailto: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: Unit unboxed tuples

2011-12-23 Thread Christian Höner zu Siederdissen
Hi,

I have to second that. I recently fell over that problem when writing
instances for certain kinds of tuples. In libraries, such as tuple
there is a special 'OneTuple' constructor but I'd really appreciate a
more uniform fix -- but don't know of one either...

Gruss,
Christian

* Ganesh Sittampalam gan...@earth.li [23.12.2011 15:39]:
 On 23/12/2011 13:46, Ian Lynagh wrote:
  On Fri, Dec 23, 2011 at 01:34:49PM +, Simon Peyton-Jones wrote:
 
  Arguments   Boxed  Unboxed
  3   ( , , )(# , , #)
  2   ( , )  (# , #)
  1  
  0   () (# #)
 
  Simple, uniform.
  
  Uniform horizontally, but strange vertically!
 
 It's worth mentioning that if you want to write code that's generic over
 tuples in some way, the absence of a case for singletons is actually a
 bit annoying - you end up adding something like a One constructor to
 paper over the gap. But I can't think of any nice syntax for that case
 either.
 
 Cheers,
 
 Ganesh
 
 ___
 Glasgow-haskell-users mailing list
 Glasgow-haskell-users@haskell.org
 http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


pgpzcDYozzaqd.pgp
Description: PGP signature
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Records in Haskell

2011-12-23 Thread Greg Weber
I am willing to help on this as much as I can. Unfortunately I don't think
you want me to lead the discussion or make decisions on this - many of
these discussions seem over my head. I will continue to study them though
and see if the sink in more.

I do think almost all of these proposals want a dot selector, so it is a
good idea for Haskell to require the normal function (composition) dot to
have spaces around it - should this be brought to the Haskell
Prime committee?

Greg Weber

On Fri, Dec 23, 2011 at 1:52 PM, Simon Peyton-Jones
simo...@microsoft.comwrote:

  Are Records stalled out again? I am perfectly willing to leave the fate
 of records up to a willing and capable implementer. That seems much better
 than waiting another 5 years for perfection :)

 ** **

 Yes, they are stalled again.  The “simple solution” turned out to be not
 simple.  I wrote it up at length in 


 http://hackage.haskell.org/trac/ghc/wiki/Records/OverloadedRecordFields***
 *

 There are various unsatisfactory aspects of the proposal, particularly
 concerning record update.  I am not sure how to resolve them. 

 ** **

 There was essentially no reaction.  As it’s quite a lot of work to
 implement, and no one seemed to care very much, I put it back on the back
 burner.   So that’s where it stands.

 ** **

 Meanwhile, AntC has put forth another proposal that I have not had time to
 look at in detail.


 http://www.haskell.org/pipermail/glasgow-haskell-users/2011-December/021298.html
 

 ** **

 *What this needs is someone (not me) to lead the discussion and try to
 make sure it makes progress*.  For example, does AntC’s proposal work? Is
 it better than the one I articulated?  Are any other variants worth
 considering? Is the gain from overloading record fields worth the pain or
 design and implementation?Volunteers, stand forth!

 ** **

 Simon

 ** **

 ** **

 *From:* Greg Weber [mailto:g...@gregweber.info]
 *Sent:* 09 December 2011 19:38
 *To:* Simon Peyton-Jones
 *Cc:* Wolfgang Jeltsch; glasgow-haskell-users@haskell.org

 *Subject:* Re: Records in Haskell

  ** **

 Are Records stalled out again? I am perfectly willing to leave the fate of
 records up to a willing and capable implementer. That seems much better
 than waiting another 5 years for perfection :)

 ** **

 As an intermediate step, is it possible to put a warning in 7.4 when the
 dot operator is used without a space so that it can be reserved for usage
 with a records solution? Or will the new records solution be turned on by
 an extension anyways?

 ** **

 On Mon, Nov 7, 2011 at 10:21 AM, Simon Peyton-Jones simo...@microsoft.com
 wrote:

 | would inclusion of such a record system into GHC mean that plans for
 | first-class labels (http://tinyurl.com/7fppj32) are abandoned? That
 | would be a pity, since first-class labels are very useful to implement
 | record systems that go beyond what the abovementioned record system
 | provides. See, for example, my work on records:
 |  
 http://www.informatik.tu-cottbus.de/~jeltsch/research/ppdp-2010-paper.pdf
 |  http://hackage.haskell.org/package/records

 The story is summarised at
http://hackage.haskell.org/trac/ghc/wiki/Records

 First-class labels are one point in the vast swamp of competing and
 overlapping proposals for records.  I think they are summarise here:
http://hackage.haskell.org/trac/ghc/wiki/ExtensibleRecords
 I am unsure which of this list of proposals you are referring to. The URL
 you quote is this
http://hackage.haskell.org/trac/haskell-prime/wiki/FirstClassLabels
 but it doesn't seem to actually contain a design, merely some options for
 a design that is implicit.  If you do have a design you advocate, it would
 be good to add it to the list at
http://hackage.haskell.org/trac/ghc/wiki/ExtensibleRecords
 perhaps explaining which of the other members of the list it subsumes.

 Because there are so many proposals I have not gone ahead with any of
 them.  The most recent thread, articulated at
http://hackage.haskell.org/trac/ghc/wiki/Records
 is to ask what is the *smallest change* that would solve the *most
 pressing problem*, namely the inability to use the same field name in
 different records.  First class labels is (I assume) much more ambitious.
  But maybe not.

 Anything you can do to bring clarity to the swamp, by editing the above
 two pages, would be a great service to the community.  At the moment, we
 are stuck in an infinite loop.

 Simon


 ___
 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: Unit unboxed tuples

2011-12-23 Thread Tyson Whitehead
On December 23, 2011 09:37:04 Ganesh Sittampalam wrote:
 On 23/12/2011 13:46, Ian Lynagh wrote:
  On Fri, Dec 23, 2011 at 01:34:49PM +, Simon Peyton-Jones wrote:
  Arguments   Boxed  Unboxed
  3   ( , , )(# , , #)
  2   ( , )  (# , #)
  1
  0   () (# #)
 
 It's worth mentioning that if you want to write code that's generic over
 tuples in some way, the absence of a case for singletons is actually a
 bit annoying - you end up adding something like a One constructor to
 paper over the gap. But I can't think of any nice syntax for that case
 either.

I believe python uses (expr,) (i.e., nothing following the ,) to distinguish a 
singelton tupple from a braced term.  Not great, but possibly not that bad.

The other option you could do is introduce another unambiguous brace symbol 
for tupples.  The new symbol would be optional except for the singelton.

(- expr, expr, expr -)  =  (expr, expr, expr)
(- expr, expr -)  =  (expr, expr)
(- expr -)  =  unable to express
(- -)  =  ()

Nothing has to be done for (# #) as it doesn't have the ambiguity.

Cheers!  -Tyson

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


Re: Unit unboxed tuples

2011-12-23 Thread Stefan Holdermans
 Here are the kinds of the type constructors:
  
 (,,) :: * - * - * - *
 (,) :: * - * - *
 () :: *
  
 (# ,, #) :: * - * - * - #
 (# , #) :: *  - * - #
 BUT
 (#  #) :: * - #

Just of out curiosity, what would be a compelling use case for singleton and 
unit unboxed tuples?

Cheers,

  Stefan

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


Re: ANNOUNCE: GHC 7.4.1 Release Candidate 1

2011-12-23 Thread Antoine Latter
One more code sample which compiled with GHC 7.2.1 and does not with the new RC:


{-# LANGUAGE FlexibleContexts, FlexibleInstances,
FunctionalDependencies, MultiParamTypeClasses, RankNTypes,
UndecidableInstances, TypeFamilies  #-}

newtype MyMonadT m a = MyMonadT (m a)

class MyClass b m | m - b where
data StM m :: * - *
myFunc :: b a - m a

instance MyClass b m = MyClass b (MyMonadT m) where
newtype StM (MyMonadT m) b = StMMine [b]
myFunc = undefined


In the instance, in GHC 7.2 the 'b' on the LHS of the newtype
introduces a fresh type binding. In the RC I get a kind error, because
the compiler seems to be trying to make all of the 'b' labeled types
the same type.

Since the 'b' isn't an indexing parameter, it doesn't make since for
it to not introduce a new binding.

This seems like an odd UI corner case, so I'm not sure what the
correct answer is. But it is a regression, so I thought I would ask
and make sure it was on purpose.

Antoine

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


filename corruption with -osuf in ghc-7.0.3

2011-12-23 Thread Evan Laforge
I've noticed a strange behaviour with ghc's -osuf flag:

% cat Test.hs
{-# LANGUAGE ForeignFunctionInterface #-}
module Test where
import Foreign
foreign import ccall wrapper c_callback :: Int - IO (FunPtr Int)
% ghc-7.0.3 -v -c -osuf .hs.o Test.hs
% ls
Tes_stub.hs.o  Test.hsTest_stub.c
Test.hiTest.hs.o  Test_stub.h

Notice that the .o for the _stub.c has acquired the .hs.o suffix, but
the last 't' of 'Test' was chopped off.

I tried the same test with the latest ghc-7.4, and it doesn't generate
a Test_stub.c at all, though there is a Test_stub.h.  But I guess it
sidesteps the question of whether -osuf should apply to the _stub.c (I
feel like it shouldn't, since it's a c file compiled by cc, not by
ghc).

I'm curious about why ghc no longer seems to need _stub.c files.  I'd
test in more details, but runghc ghci for 7.4 is segfaulting
unpredictably so I think there are larger problems here.

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