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 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 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: 7.4.1-pre: Show Integral

2011-12-22 Thread Simon Peyton-Jones
|  2011/12/22 Edward Kmett ekm...@gmail.com:
|   The change, however, was a deliberate _break_ with the standard that
|   passed through the library review process a few months ago, and is now
|   making its way out into the wild.
|  
|  Is it reasonable to enquire how many standard-compliant implementations
|  of Haskell there are?

Just to be clear, the change IS the standard.  GHC has to change to be 
compliant.  At least that's how I understand it.

Simon


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


RE: Unexpected list non-fusion

2011-12-15 Thread Simon Peyton-Jones
| Am Montag, den 12.12.2011, 15:37 -0500 schrieb wren ng thornton:
|  I've noticed that take and filter are good producers (and consumers)
|  for list fusion, but takeWhile, drop, and dropWhile are not. Is there
|  any reason for this discrepancy?
| 
|  If not, would I need to go through the libraries@ process for fixing
|  it, or should I just submit a patch?

Please just submit a patch.

| while preparing my guest lecture¹ about Haskell Performance recently I also
| noticed that takeWhile (and concatMap!) are not setup for list fusion, here
| is what I showed the students; it improved performance considerably in the
| testcase.
| 
| takeWhile' :: (a - Bool) - [a] - [a]
| takeWhile' p xs = build $ \c n - foldr (takeWhileF p c n) n xs {-# INLINE
| takeWhile' #-}
| 
| takeWhileF p c n x xs = if p x then x `c` xs else n
| 
| Of course, for a proper inclusion one first has to find out if takeWhile' is
| sufficiently fast even when not fused, or whether one has to do the „replace
| first, try to fuse, and then try to replace back by original function if not
| fused“ tick that is used for, e.g., (++).

The latter approach is probably safer.  Follow the pattern for (++).

Thanks

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


RE: Revert a CAF?

2011-12-06 Thread Simon Peyton-Jones
GHCi does this somehow, so it's definitely possible; Simon M will know.

|  -Original Message-
|  From: glasgow-haskell-users-boun...@haskell.org 
[mailto:glasgow-haskell-users-
|  boun...@haskell.org] On Behalf Of wren ng thornton
|  Sent: 06 December 2011 17:49
|  To: GHC-users List
|  Subject: Revert a CAF?
|  
|  So, I have an optimization/internals question. Does the GHC API have any
|  hooks for being able to revert a CAF to the original expression, thus
|  discarding the previously computed result?
|  
|  The reason I'm wanting this is that I have a particular CAF which is an
|  infinite list. Unfolding that list takes a fair deal of work, so we want
|  to share it whenever possible; however it doesn't take an overwhelming
|  amount of work, so if we know we've evaluated more of the list than
|  necessary (for a long while), it'd be nice to be able to revert the
|  evaluation in order to save on memory overhead (e.g., by calling relax
|  :: IO()).
|  
|  I could hack something together based on unsafePerformIO and top-level
|  IORefs, and it's clear that this is in fact a safe thing to do, but I'm
|  worried about the semantic issues inherent in unsafePerformIOed
|  top-level IORefs (e.g., the fact that their scope isn't particularly
|  well defined: is it per library instance? per runtime?...).
|  Unfortunately, for what I'm doing, it isn't really feasible to just
|  leave the IO type in there nor to pass around the infinite list so we
|  can use scoping rules to decide when to free it.
|  
|  (Feel free to offer alternative suggestions to handling this situation too.)
|  
|  --
|  Live well,
|  ~wren
|  
|  ___
|  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: Why not allow empty record updates?

2011-11-16 Thread Simon Peyton-Jones
|  Trouble is, what type does this have?
|f x = x {}
| 
|  Malcolm Wallace wrote:
|  f :: a -  a
| 
|  Ian Lynagh wrote:
|  That wouldn't help the original poster, as it is incompatible with
|  f :: Foo Clean -  Foo Dirty

There are several different things going on in this thread.

1.  What does  f x = x {} mean?  The report 
http://www.haskell.org/onlinereport/haskell2010/haskellch3.html#x8-490003.15 
says we should treat it like  
   f x = case x of
   C1 a b - C1 a b
   C2 v - C2 v
but if there are no fields how do we know what C1 and C2 are?  The whole 
section only makes sense if you know x's type.  So Malcolm's suggestion of f 
:: forall a. a - a would be non-uniform with the non-empty cases.

When we *do* know the type then the above translation makes sense, and even 
allows the
f :: Foo Clean - Foo Dirty
type-change.  Now two further issues arise:

2. When do we know the type?  If the type is supposed to come from an 
enclosing type signature, to specify the type system one would need to specify 
the way that type annotations propagate. This isn't impossible (we do it for 
higher-rank types), but it seems like a big hammer for this particular nut.

3.  Edward wants to maintain sharing, meaning presumably that no fresh record 
is allocated.  That makes sense, but sadly System FC (GHC's intermediate 
language) has no way to express it.  We'd need some new axioms claiming that   
forall ab. Foo a ~ Foo b.  But that's a question for another time.  Moreover, 
it affects non-record types just as much.

Simon

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


RE: Why not allow empty record updates?

2011-11-15 Thread Simon Peyton-Jones
Hmm yes. Fair enough.  Does anyone care enough?  I can see (now) that it 
wouldn't really be hard.

| -Original Message-
| From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-users-
| boun...@haskell.org] On Behalf Of Yitzchak Gale
| Sent: 15 November 2011 11:16
| To: Malcolm Wallace
| Cc: GHC-users List
| Subject: Re: Why not allow empty record updates?
| 
| Simon Peyton-Jones wrote:
|  Trouble is, what type does this have?
|        f x = x {}
| 
| Malcolm Wallace wrote:
|  Empty record patterns {} are permitted, even for types
|  that are not declared with named fields.
|  So I don't see why an empty record update should
|  require the type to be declared with named fields either.
| 
| Yes. The translation of record updates given in the Report
| makes perfect sense for {}. It is only forbidden by
| n = 1, but no reason is given for that restriction.
| 
| According to that translation, the type of x {} is
| the type of the case expression it translates to.
| 
| Thanks,
| Yitz
| 
| ___
| 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: Why not allow empty record updates?

2011-11-15 Thread Simon Peyton-Jones
|   Trouble is, what type does this have?
|  
| f x = x {}
| 
|  f :: a - a
| 
| That wouldn't help the original poster, as it is incompatible with
| f :: Foo Clean - Foo Dirty

Ah!  *That* is why I said it was awkward.  Thanks Ian. 

Simon

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


RE: instance union proposal

2011-11-15 Thread Simon Peyton-Jones
Serge

I'm afraid I don't really follow your proposal in detail, but I think it may be 
a version of the proposal described here
http://hackage.haskell.org/trac/ghc/wiki/DefaultSuperclassInstances
Perhaps you could see if the design there would meet your goals.

Simon

|  -Original Message-
|  From: glasgow-haskell-users-boun...@haskell.org 
[mailto:glasgow-haskell-users-
|  boun...@haskell.org] On Behalf Of Serge D. Mechveliani
|  Sent: 12 November 2011 10:51
|  To: glasgow-haskell-users@haskell.org
|  Subject: instance union proposal
|  
|  Dear Haskell implementors,
|  
|  I suggest the following small extension to the instance declaration in
|  the language. So far -- for  Haskell + glasgow-ext.
|  I think that they are easy to implement.
|  This is the  instance union  proposal.
|  It is needed to write shorter several `old' instance declarations.
|  This will make programs easier to read.
|  It suggests the so-called
| inherited decl  and, more general,  union decl.
|  
|  Inherited instance decl proposal
|  
|  
|  Union several instance declarations with the same condition part and such
|  that among the conclusion  classes there exists some which inherits all
|  others.
|  Example 1.  My program uses the class tower
|  
| Field a Picture 1.
| |
| ERing
| |
| CRing a
| |
| Ring a
|/\
|  AddGroup a  MulSemigroup a
|   |  |
|  AddSemigroup a  |
|   \ /
|Set a
|  
|  -- | means that the upper inherits from the lower.
|  Now, by the application meaning, I need to write
|  
|instance (Show a, CRing a) = CRing (Pol a)
|  where
|  implement operations of Set
|  implement operations of AddGroup
|  ...
|  implement operations of CRing
|  
|  From the class decls it is clear to the compiler that  CRing  inherits
|  all that is lower on the picture. Therefore, the conditional
|  `instance (Show a, CRing a) =' and 'where'
|  is written only once.
|  In the existing language, I need to write this conditional 6 times.
|  
|  
|  Union instance decl proposal
|  
|  
|  It is a generalization for  inhereted decl.
|  
|  instances (cond_1, ..., cond_n) -- of the type parameters a_1 ... a_m
|=
|typeTuple (params)  has  {conclInstList}
|where
|implement operations for each member of conclInstList.
|  
|  It differs from the old instance declaration in that
|  1) it unions several old declarations having the same conditional part,
|  2) each member of conclInstList can be conditional,
|  3) in conclInstList it can be skipped any instance which is inherited
| by some other member in this list.
|  
|  params is a subset of {a_1 ... a_m},
|  typeTuple (params)
|  is a tuple of type expressions, as in old declaration,
|  for example,  `(a, b)', `Vector a', `[(a,b), Vector a]'.
|  It is the argument for the conclusion instance declarations.
|  
|  conclInstList is a list of inst-members separated by comma.
|  Each member of  conclInstList  is either an
|  old  conclusion instance declaration
|  or a conditional declaration.
|  
|  Example.
|  In the situtation of  Picture 1,  I need to declare
|  
|instance (Show a, CRing a) =
| (Pol a) has { CRing,  if (has a Field) then ERing }
|  where
|  define operations for  Set (Pol a)
|  define operations for  AddSemigroup (Pol a)
|  ...
|  define operations for  CRing (Polynomial a)
|  
|  define operations for  ERing (Pol a)  -- this part has the
|-- additional condition  (Field a)
|  
|  Its meaning is that the complier extends this into several `old'
|  instance declarations:
|instance (Show a, CRing a) = Set (Pol a) where
|  define operations for  Set (Pol a)
|...
|instance (Show a, CRing a) = CRing (Pol a) where
|  define operations for  Set (Pol a)
|  
|instance (Show a, Field a) = ERing (Pol a) where
|define operations for  ERing (Pol a)
|  
|  (in the last decl `Field a' has been moved to LHS).
|  
|  In this example  typeTuple === (Pol a).
|  For bi-parametric instances, the concusion part may be, for example
|=
|[a, Pol a] has {Foo1, Foo2} ...
|  
|  This means the two instance assertions  Foo1 a (Pol a),  Foo a (Pol a),
|  and `[a, Pol a]' is the agrument tuple for the instance conclusions.
|  
|  
|  This is a draft proposal. If the idea is accepted, some generalizations
|  and 

RE: Why not allow empty record updates?

2011-11-14 Thread Simon Peyton-Jones
Trouble is, what type does this have?

f x = x {}

In your example the type annotations give the clue, but Haskell is mainly 
designed for type annotations to be optional.  We require at least one field so 
we can figure out, from the field name, which type is being updated.

Yes, something could doubtless be done by following the type annotations, much 
like higher-rank types, but it would be somewhat tricky to specify -- and the 
whole feature of type-changing update is (as you know) a bit obscure and not 
widely used, so it'd be adding complexity to an already-dark corner.  

See also the (inconclusive) discussion here, which would involve abolishing the 
entire type-changing update mechanism entirely!  
http://hackage.haskell.org/trac/ghc/wiki/Records

Simon

|  -Original Message-
|  From: glasgow-haskell-users-boun...@haskell.org 
[mailto:glasgow-haskell-users-
|  boun...@haskell.org] On Behalf Of Herbert Valerio Riedel
|  Sent: 14 November 2011 14:31
|  To: glasgow-haskell-users@haskell.org
|  Subject: Why not allow empty record updates?
|  
|  Hello GHC HQ,
|  
|  I have been toying with phantom types in combination with polymorphic
|  record-updates (which is a great feature imho), but stumbled over a
|  limitation: GHC doesn't allow empty record updates (see toy example
|  below), and I couldn't find a GHC language extension to relax this
|  constraint. In the toy-example below it was easy to workaround by
|  performing a dummy record update, but for more advanced uses workarounds
|  becomes a bit more annoying.
|  
|  Is there a particular reason why empty record updates are disallowed by
|  the Haskell Report? Would it be sensible, to allow empty record updates
|  as a GHC language extension?
|  
|  
|  hvr.
|  
|  ---
|  -- empty types for tagging
|  data Clean
|  data Dirty
|  
|  data Foo a = Foo { fa :: Int, fb :: String }
|  data Bar a = Bar { ba :: Int, bb :: Foo a }
|  
|  markDirtyFoo :: Foo Clean - Foo Dirty
|  markDirtyFoo foo = foo { } -- rejected with Empty record update error
|  markDirtyFoo foo = foo { fa = fa foo } -- workaround: dummy update
|  
|  markDirtyBar :: Bar Clean - Bar Dirty
|  markDirtyBar bar = bar { bb = markDirtyFoo (bb bar) } -- works
|  
|  
|  
|  
|  
|  
|  ___
|  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: Records in Haskell

2011-11-07 Thread Simon Peyton-Jones
Wolfgang

Is there a wiki page giving a specific, concrete design for the proposal you 
advocate?  Something at the level of detail of 
http://hackage.haskell.org/trac/ghc/wiki/Records/OverloadedRecordFields?

I am unsure whether you regard it as an alternative to the above, or something 
that should be done as well.   And if the former, how does it relate to the 
challenge articulated on http://hackage.haskell.org/trac/ghc/wiki/Records, 
namely how to make Haskell's existing named-field system work better?

Thanks

Simon




|  -Original Message-
|  From: glasgow-haskell-users-boun...@haskell.org 
[mailto:glasgow-haskell-users-
|  boun...@haskell.org] On Behalf Of Wolfgang Jeltsch
|  Sent: 07 November 2011 18:31
|  To: glasgow-haskell-users@haskell.org
|  Subject: Re: Records in Haskell
|  
|  Am Montag, den 07.11.2011, 17:53 + schrieb Barney Hilken:
|   Here is my understanding of the current state of the argument:
|  
|   Instead of Labels, there will be a new kind String, which is not a
|   subkind of *, so its elements are not types. The elements of String
|   are strings at the type level, written just like normal strings. If
|   you want labels, you can define them yourself, either empty:
|  
|  data Label (a :: String)
|  
|   or inhabited
|  
|  data Label (a :: String) = Label
|  
|   these definitions give you a family of types of the form Label name,
|   in the first case empty (except for undefined), in the second case
|   inhabited by a single element (Label :: Label name)
|  
|   There are several similar proposals for extensible records defined
|   using labels, all of which (as far as I can see) could be defined just
|   as easily using the kind String.
|  
|  The problem with this approach is that different labels do not have
|  different representations at the value level. In my record system, I use
|  label definitions like the following ones:
|  
|  data MyName1 = MyName1
|  
|  data MyName2 = MyName2
|  
|  This allows me to pattern match records, since I can construct record
|  patterns that contain fixed labels:
|  
|  X : MyName1 := myValue1 : MyName2 := myValue2
|  
|  I cannot see how this could be done using kind String. Do you see a
|  solution for this?
|  
|  A similar problem arises when you want to define a selector function.
|  You could implement a function get that receives a record and a label as
|  arguments. However, you could not say something like the following then:
|  
|  get myRecord MyName1
|  
|  Instead, you would have to write something like this:
|  
|  get myRecord (Label :: MyName1)
|  
|  Whis is ugly, I’d say.
|  
|  Yes, Simon’s proposal contains syntactic sugar for selection, but this
|  sugar might not be available for other record systems, implemented in
|  the language.
|  
|  The situation would be different if we would not only have kind String,
|  but also an automatically defined GADT that we can use to fake dependent
|  types with string parameters:
|  
|  data String :: String - *  -- automatically defined
|  
|  A string literal abc would be of type String abc then. However, I am
|  not sure at the moment, if this would solve all the above problems.
|  
|  Best wishes,
|  Wolfgang
|  
|  
|  ___
|  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: problems with impredicativity

2011-11-05 Thread Simon Peyton-Jones
Wolfgang

Dimitrios, Stephanie and I spent a long time trying to come up with a decent 
story for impredicative polymorphism (which would let you use types like 
[forlall a. a-a]), wrote several papers about it, and even implemented one 
version in GHC (hence -XImpredicativeTypes).

However the implementation was Just Too Complicated, and its specification was 
too unpredictable.  So during the last major overhaul of the type inference 
engine, I took most of it out. 

The most promising approach is, I think, Dimitrios and Claudio's QML idea 
(http://research.microsoft.com/en-us/um/people/crusso/qml/).  It's less 
ambitious than our earlier schemes, but it is much simpler.

GHC currently implements a kind of half-way house. We have simply not devoted 
serious attention to the story for impredicative types, yet.  Too busy with 
type functions and other stuff that has seemed more immediately useful.  So I'm 
afraid I make no warranty for a sensible, predicable behaviour when you are 
using impredicativity.

If you care about this, add yourself to the cc list for the ticket
http://hackage.haskell.org/trac/ghc/ticket/4295
explain why it's important to you, and attach a test case showing the kind of 
thing you wanted to be able to do.  The more motivating examples, the greater 
the incentive to fix it.

Simon

|  -Original Message-
|  From: glasgow-haskell-users-boun...@haskell.org 
[mailto:glasgow-haskell-users-
|  boun...@haskell.org] On Behalf Of Wolfgang Jeltsch
|  Sent: 04 November 2011 22:13
|  To: glasgow-haskell-users@haskell.org
|  Subject: problems with impredicativity
|  
|  Hello,
|  
|  this code is accepted by GHC 7.0.4:
|  
|   {-# LANGUAGE ImpredicativeTypes #-}
|  
|   polyId :: (forall a. a) - a
|   polyId x = x
|  
|   polyIdMap :: [forall a. a] - [forall a. a]
|   polyIdMap xs = fmap polyId xs
|  
|  However, this one isn’t:
|  
|   {-# LANGUAGE ImpredicativeTypes #-}
|  
|   polyId :: (forall a. Maybe a) - Maybe a
|   polyId x = x
|  
|   polyIdMap :: [forall a. Maybe a] - [forall a. Maybe a]
|   polyIdMap xs = fmap polyId xs
|  
|  Is there a way to make it accepted?
|  
|  Best wishes,
|  Wolfgang
|  
|  
|  ___
|  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: :kind broken in HEAD

2011-10-25 Thread Simon Peyton-Jones
Thanks; fixed

From: sean.leat...@gmail.com [mailto:sean.leat...@gmail.com] On Behalf Of Sean 
Leather
Sent: 22 October 2011 16:24
To: GHC Users List
Cc: Simon Peyton-Jones
Subject: :kind broken in HEAD

It seems like :kind is broken in the HEAD ghci:

*Main :kind Maybe

Top level:
Expecting an ordinary type, but found a type of kind * - *
In a type expected by the context: Maybe
*Main

Simon, could this be related to your change for :kind! ?

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


RE: Records in Haskell

2011-10-20 Thread Simon Peyton-Jones
| Subject: Re: Records in Haskell
| 
| I have added my proposal to the wiki.The only downsides to it that I can see 
are:

Thanks to Barney for articulating a proposal for records in Haskell.  Over 
various plane rides and ICFP chats I've worked out some more details.  It's not 
as simple as I'd hoped. 

I'm underwater with stuff at the moment but I did find the time to capture a 
summary here
http://hackage.haskell.org/trac/ghc/wiki/Records/OverloadedRecordFields

Please do correct errors, suggest solutions, or explore variants.

Simon

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


RE: Two Proposals

2011-10-18 Thread Simon Peyton-Jones
For example the following code fragments read well:

then group inits
then group permutations
then group subsequences
then group tails

Yes... not quite so well with the by variants.  What would we say?
  then group initsBy by x


But following the aforementioned naming convention the groupWith function could 
as well be named as equals. Now this reads well:

then group equals by e

Good idea.  But equals is a terribly over-used word; I think using it would 
cause confusion.  How about equalities, or equivalents :: [a] - [[a]]

I don't think we can steal group as a keyword -- it's a function exported by 
Data.List, and I don't think the benefit justifies the cost.

Simon

From: George Giorgidze [mailto:giorgi...@gmail.com]
Sent: 10 October 2011 23:22
To: Simon Peyton-Jones; GHC Users List; Philip Wadler
Subject: Re: Two Proposals

A quick thought that came to me after hoogling [a] - [[a]].

The first four functions in the search result are named after what they return 
(noun in plural) rather than what they do (verb). I am talking about inits, 
permutations, subsequence and tails.

So I thought the following syntax might work as well if (as it is already 
common) grouping functions are named after  what they return.

then   f
then   f by e
then group f
then group f by e

For example the following code fragments read well:

then group inits
then group permutations
then group subsequences
then group tails

Here we use the special identifier group as a verb.

I have not told you about the fifth result of the hoogling, the groupWith 
function. The following really looks ugly:

then group groupWith by e

But following the aforementioned naming convention the groupWith function could 
as well be named as equals. Now this reads well:

then group equals by e

Cheers, George


On 2011-Oct-5, at 09:14 , Simon Peyton-Jones wrote:


[adding ghc-users]

It's not easy, Phil.  Do you have any ideas?

For the 'then' case the name of the function serves as the verb.  One might say

  then take 4
or
  then takeWhile by salary  40

For grouping one might like to say the same  thing, such as
  then groupBy by salary
but the typing rule is quite different, so we really need a different keyword.  
We chose the compound keyword then group to avoid needing a whole new keyword 
(group is treated specially only in tthis context). So you write
  then group by salary using groupBy

Using this order of the pieces for the sorting case is harder. What would one 
say?  then process?  Like this?
  then process by salary  40 using takeWhile
Not very nice.

One could use a new keyword for grouping theng say, thus:
  theng groupBy by salary
But that is hardly beautiful either.

So the current story is not great, but it's the best I could think of. 
Improvements welcome.

Simon

|  -Original Message-
|  From: Philip Wadler [mailto:wad...@inf.ed.ac.uk]
|  Sent: 04 October 2011 18:15
|  To: Simon Peyton-Jones; George Giorgidze
|  Subject: Re: FW: Two Proposals
|
|  George,
|
|  Nice proposal.  I like the idea of symmetry, but don't at all like the
|  idea that f comes before e for 'then' but f comes after e for 'then
|  group'.  Can you rethink it and come up with something even more
|  symmetric?
|
|  Yours,  -- P
|
|
|  On Tue, Oct 4, 2011 at 9:23 AM, Simon Peyton-Jones
|  simo...@microsoft.commailto:simo...@microsoft.com wrote:
|   FYI
|  
|   -Original Message-
|   From: 
glasgow-haskell-users-boun...@haskell.orgmailto:glasgow-haskell-users-boun...@haskell.org
 [mailto:glasgow-haskell-
|  users-boun...@haskell.org] On Behalf Of George Giorgidze
|   Sent: 30 September 2011 18:28
|   To: 
glasgow-haskell-users@haskell.orgmailto:glasgow-haskell-users@haskell.org
|   Subject: Two Proposals
|  
|   GHC Users,
|  
|   I would like to make to the following two proposals:
|* Eliminate the default grouping close from SQL-like comprehensions
|* Introduce a GHC extension for list literal overloading
|  
|   OK, let me start with the first proposal.
|  
|   Currently, the SQL-like comprehension notation (both in its list 
comprehension
|  and monad comprehension variants) features the following five clauses:
|  
|   then f
|   then f by e
|   then group by e
|   then group using f
|   then group by e using f
|  
|   The first two clauses are used for specifying transformations of type [a] 
- [a]
|  (or Monad m = m a- m a for monad comprehensions). The following three
|  clauses are used for specifying transformations of type [a] - [[a]] (or 
Monad m,
|  Functor f = m a - m (f a) for monad comprehensions). See [1] for further
|  details.
|  
|   Note that the third clause does not mention which function is used for 
grouping.
|  In this case GHC.Exts.groupWith function is used as a default for list
|  comprehensions and the mgroupWith function from the MonadGroup class is used
|  as a default for monad comprehensions.
|  
|   I would like to suggest to remove

RE: Implementing a new Primop, stage1 panic

2011-10-17 Thread Simon Peyton-Jones
Paul

Always switch on -dcore-lint; it's a self-checker for types, and usually nails 
an error much closer to the source.

Simon

From: glasgow-haskell-users-boun...@haskell.org 
[mailto:glasgow-haskell-users-boun...@haskell.org] On Behalf Of Paul Monday
Sent: 16 October 2011 16:54
To: glasgow-haskell-users@haskell.org
Subject: Implementing a new Primop, stage1 panic

(Reposting since this got cross-posted sort of oddly and I wasn't subscribed 
yet)

I'm having an odd problem as I try to define my own primop, it seems that some 
docs may be out of date with respect to all of the touch points for a simple 
primop addition.  I've followed what the various wiki pages have to offer 
(primarily 
http://hackage.haskell.org/trac/ghc/wiki/AddingNewPrimitiveOperations and 
http://hackage.haskell.org/trac/ghc/wiki/Commentary/PrimOps) without success.  
I even unraveled my PrimOp to be, basically, an exact copy of another PrimOp 
without luck.

The primop I'm attempting to add is now very, very simple and copies FloatAddOp 
exactly so there must be an additional file I have to modify before the primop 
is completely added.

Here are my simple modifications:

./compiler/prelude/primops.txt.pp
primop   FloatVAddOp   plusFloatVec#  Dyadic
   Float# - Float# - Float#
   with commutable = True

./compiler/codeGen/CgPrimOp.hs
translateOp FloatVAddOp  = Just (MO_F_Add W32)

The compiler error is below.  I have the feeling that an interface is not being 
built somewhere ... this must be a simple one but I can't find any references 
to this error anywhere ... has anyone seen this one before?

inplace/bin/ghc-stage1   -H64m -O0 -fasm-package-name ghc-7.3.20111007 
-hide-all-packages -i -icompiler/basicTypes -icompiler/cmm -icompiler/codeGen 
-icompiler/coreSyn -icompiler/deSugar -icompiler/ghci -icompiler/hsSyn 
-icompiler/iface -icompiler/llvmGen -icompiler/main -icompiler/nativeGen 
-icompiler/parser -icompiler/prelude -icompiler/profiling -icompiler/rename 
-icompiler/simplCore -icompiler/simplStg -icompiler/specialise 
-icompiler/stgSyn -icompiler/stranal -icompiler/typecheck -icompiler/types 
-icompiler/utils -icompiler/vectorise -icompiler/stage2/build 
-icompiler/stage2/build/autogen -Icompiler/stage2/build 
-Icompiler/stage2/build/autogen -Icompiler/../libffi/build/include 
-Icompiler/stage2 -Icompiler/../libraries/base/cbits 
-Icompiler/../libraries/base/include -Icompiler/. -Icompiler/parser 
-Icompiler/utils   -optP-DGHCI -optP-include 
-optPcompiler/stage2/build/autogen/cabal_macros.h -package Cabal-1.11.2 
-package array-0.3.0.3 -package base-4.4.0.0 -package bin-package-db-0.0.0.0 
-package bytestring-0.9.2.0 -package containers-0.4.2.0 -package 
directory-1.1.0.1 -package filepath-1.2.0.1 -package hoopl-3.8.7.2 -package 
hpc-0.5.1.0 -package old-time-1.0.0.7 -package process-1.1.0.0 -package 
template-haskell-2.6.0.0 -package unix-2.5.0.0  -Wall -fno-warn-name-shadowing 
-fno-warn-orphans -XHaskell98 -XNondecreasingIndentation -XCPP -XMagicHash 
-XUnboxedTuples -XPatternGuards -XForeignFunctionInterface -XEmptyDataDecls 
-XTypeSynonymInstances -XMultiParamTypeClasses -XFlexibleInstances -XRank2Types 
-XScopedTypeVariables -XDeriveDataTypeable -DGHCI_TABLES_NEXT_TO_CODE -DSTAGE=2 
-O0 -fasm  -no-user-package-conf -rtsopts -odir compiler/stage2/build 
-hidir compiler/stage2/build -stubdir compiler/stage2/build -hisuf hi -osuf  o 
-hcsuf hc -c compiler/iface/BinIface.hs -o compiler/stage2/build/BinIface.o
ghc-stage1: panic! (the 'impossible' happened)
  (GHC version 7.3.20111007 for x86_64-unknown-linux):
  applyTypeToArgs
ghc-prim:GHC.Prim.sizeofMutableArray#{(w) v 91V} [gid[PrimOp]]
  @ e{tv i4L2} [tv] ds{v i4Lc} [lid] i#{v i4Lg} [lid]
forall a{tv 12} [tv].
ghc-prim:GHC.Prim.MutableArray#{(w) tc 31m}
  e{tv i4L2} [tv] a{tv 12} [tv]
- ghc-prim:GHC.Prim.Int#{(w) tc 3G}

Paul Monday
Parallel Scientific, LLC.
paul.mon...@parsci.commailto:paul.mon...@parsci.com




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


RE: Is this a concurrency bug in base?

2011-10-12 Thread Simon Peyton-Jones
Did you try 7.2?  As I mentioned, the issue should have gone away entirely 
because there is no shared cache any more

Simon

From: glasgow-haskell-users-boun...@haskell.org 
[mailto:glasgow-haskell-users-boun...@haskell.org] On Behalf Of Jean-Marie 
Gaillourdet
Sent: 12 October 2011 07:19
To: wagne...@seas.upenn.edu; Daniel Fischer
Cc: glasgow-haskell-users@haskell.org
Subject: Re: Is this a concurrency bug in base?

Hi,

I've continued my search for a proper workaround. Again, I did find some 
unexpected results. See below.

On 09.10.2011, at 17:56, wagne...@seas.upenn.edu wrote:

 Quoting Jean-Marie Gaillourdet j...@gaillourdet.net:

 That sounds plausible. Do you see any workaround? Perhaps repeatedly 
 evaluating typeOf?

 If there's a concurrency bug, surely the workaround is to protect calls to 
 the non-thread-safe function with a lock.

  typeOfWorkaround lock v = do
  () - takeMVar lock
  x - evaluate (typeOf v)
  putMVar lock ()
  return x

 ~d

This is my previous program with your workaround, it is also attached as 
TypeRepEqLock.hs

import Control.Concurrent
import Control.Exception
import Control.Monad
import Data.Typeable
import System.IO.Unsafe

main :: IO ()
main =
do { fin1 - newEmptyMVar
  ; fin2 - newEmptyMVar

  ; forkIO $ typeOf' () = putMVar fin1
  ; forkIO $ typeOf' () = putMVar fin2

  ; t1 - takeMVar fin1
  ; t2 - takeMVar fin2
  ; if (t1 /= t2)
  then putStrLn $ typeOf  ++ show t1 ++  /= typeOf  ++ show t2
  else putStrLn Ok
  }


{-# NOINLINE lock #-}
lock :: MVar ()
lock = unsafePerformIO $ newMVar ()

-- Ugly workaround to http://hackage.haskell.org/trac/ghc/ticket/5540
typeOf' :: Typeable a = a - IO TypeRep
typeOf' x =
do { () - takeMVar lock
  ; t - evaluate $ typeOf x
  ; putMVar lock ()
  ; return t
  }


Compile and execute:

$ ghc-7.0.3 -threaded -rtsopts TypeRepEqLock.hs
snip
$ while true ; do ./TypeRepEqLock +RTS -N ; done
Ok
Ok
Ok
Ok
Ok
Ok
Ok
Ok
Ok
TypeRepEqLock: thread blocked indefinitely in an MVar operation
Ok
Ok
Ok
^C^C

I'm sorry but I don't see how this program could ever deadlock, unless there is 
some more locking in typeOf and (==) on TypeReps.

On the other side, my admittedly ugly workaround works fine for hours and hours.

import Control.Concurrent
import Control.Exception
import Control.Monad
import Data.Typeable

main :: IO ()
main =
do { fin1 - newEmptyMVar
  ; fin2 - newEmptyMVar

  ; forkIO $ return (typeOf' ()) = evaluate = putMVar fin1
  ; forkIO $ return (typeOf' ()) = evaluate = putMVar fin2

  ; t1 - takeMVar fin1
  ; t2 - takeMVar fin2
  ; if (t1 /= t2)
  then putStrLn $ typeOf  ++ show t1 ++  /= typeOf  ++ show t2
  else putStrLn Ok
  }

typeOf' val
  | t1 == t2 = t1
  | otherwise = typeOf' val
where
  t1 = typeOf'' val
  t2 = typeOf''' val
{-# NOINLINE typeOf' #-}


typeOf'' x = typeOf x
{-# NOINLINE typeOf'' #-}
typeOf''' x = typeOf x
{-# NOINLINE typeOf''' #-}


$ ghc-7.0.3 -threaded -rtsopts TypeRepEq.hs
snip
$ while true ; do ./TypeRepEq +RTS -N ; done
Ok
Ok
Ok
Ok
Ok
Ok
…

Any hints how to avoid the thread blocked indefinitely in an MVar operation 
exception?

Cheers,
Jean

___
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: Unwanted eta-expansion

2011-10-12 Thread Simon Peyton-Jones
Roman, Jan-Willem

I'm maxed out at the moment, and will be so for at least a week.

If you think there is something mysterious and J-W agrees, could you create a 
ticket, with the smallest example you can, and instructions to reproduce?   
That'd be brilliant.

Of course, Jan-Willem, if you have a moment to diagnose a bit more about WHY 
it's going slower that would be even better!

Thanks

Simon

| -Original Message-
| From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-users-
| boun...@haskell.org] On Behalf Of Jan-Willem Maessen
| Sent: 10 October 2011 02:51
| To: Roman Cheplyaka
| Cc: glasgow-haskell-users@haskell.org
| Subject: Re: Unwanted eta-expansion
| 
| On Sun, Oct 9, 2011 at 10:54 AM, Roman Cheplyaka r...@ro-che.info wrote:
|  * Jan-Willem Maessen jmaes...@alum.mit.edu [2011-10-08 12:32:18-0400]
|  It seems to be a common misconception that eta-abstracting your
|  functions in this way will speed up or otherwise improve your code.
| 
|  Simon PJ has already provided a good explanation of why GHC eta
|  expands.  Let me take another tack and describe why the code you wrote
|  without eta expansion probably doesn't provide you with any actual
|  benefit.  Roughly speaking, you're creating a chain of closures whose
|  contents exactly describe the contents of your list (ie you've created
|  something that's isomorphic to your original list structure), and so
|  you should expect no benefit at all.
| 
|  Thanks for the analysis.
| 
|  I used myFoldl as a minimal example to ask the question.
| 
|  Here's an example of real code where this does make a difference:
|  https://github.com/feuerbach/regex-
| applicative/tree/03ca9c852f06bf9a9d51505640b8b72f07291c7d
| 
| Ah, now things get more complicated!  :-)  I suspect here you're
| actually entering the regexp closures, and compiling it down is
| actually saving you a teensy bit of interpretive overhead.
| 
|  ...
|  What's even more interesting (and puzzling!), if remove
|  -fno-do-lambda-eta-expansion for Text/Regex/Applicative/Types.hs,
|  the benchmark takes 2.82 seconds.
| 
| That *Is* odd.  The only obvious code generated here would be the
| newtype instances, for which this should surely be irrelevant?  Can
| someone at GHC HQ explain this one?
| 
| -Jan
| 
| ___
| 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: Is this a concurrency bug in base?

2011-10-10 Thread Simon Peyton-Jones
Thank you for the detailed investigation.  I have not followed all the details 
of this thread, but I think that it may (happily) represent a bug in generating 
TypeReps that is already fixed.


· We used to have a global cache from which we generated unique Int 
keys corresponding to type constructors.  The trouble with this was that (a) 
you weren’t guaranteed to get the same key in every run, and (b) the cache was 
not initially designed to be thread-safe, and I’m not sure that we’d closed all 
race conditions.


· But NOW we generate a MD5 hash, or fingerprint, of the type.  So 
there is no global cache, no race condition, and you should get the same 
behaviour ever time.

In short, can you try with 7.2?

Thanks

Simon

From: glasgow-haskell-users-boun...@haskell.org 
[mailto:glasgow-haskell-users-boun...@haskell.org] On Behalf Of Jean-Marie 
Gaillourdet
Sent: 09 October 2011 12:53
To: glasgow-haskell-users
Subject: Is this a concurrency bug in base?

Hi,

I am working on a library I'd like to release to hackage very soon, but I've 
found a problem with supporting GHC 6.12 and GHC 7.0.
Consider the following program:

import Control.Concurrent
import Data.Typeable

main :: IO ()
main =
 do { fin1 - newEmptyMVar
; fin2 - newEmptyMVar

; forkIO $ typeRepKey (typeOf ()) = print  putMVar fin1 ()
; forkIO $ typeRepKey (typeOf ()) = print  putMVar fin2 ()

; () - takeMVar fin1
; () - takeMVar fin2
; putStrLn ---
; return ()
}

When compiled with GHC 7.0.x or GHC 6.12.x, it should print two identical 
numbers. Sometimes it does not.
To reproduce this compile and execute as follows:

$ ghc-7.0.3 -rtsopts -threaded TypeRepKey.hs -o TypeRepKey
$ while true ; do ./TypeRepKey +RTS -N  ; done
0
0
---
0
0
---
0
0
---
0
1
---
0
0
---
…

Ideally you should get an infinite number of zeros but once in a while you have 
a single(!) one in between. The two numbers of one program run should be 
identical, but their values may be arbitrary. But it should not be possible to 
have single outliers.

This only happens when executed with more than one thread. I've also a somewhat 
larger program which seems to indicate that fromDynamic fails occasionally. I 
can post it as well if it helps. This seems to be a Heisenbug as it is 
extremely fragile, when adding a | grep 1 to the while loop it seems to 
disappears. At least on my computers.

All this was done on several Macs running the latest OS X Lion with ghc 7.0.3 
from the binary distribution on the GHC download page.

Actually, I am trying to find a method to use a type as key in a map which 
works before GHC 7.2. I'd be glad to get any ideas on how to achieve that, 
given that typeRepKey seems to buggy.

 I'd be happy to get any comments on this matter.

Regards,
  Jean
___
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: log time instead of linear for case matching

2011-10-10 Thread Simon Peyton-Jones
Greg

In GHC, big cases are done as tables (if dense) or trees (if sparse).  If you 
have some examples where things go bad, do submit a bug report.

For big dispatches on strings, I'm pretty sure we do something linear, top to 
bottom.   I'd be strongly inclined to use a proper Map structure if you want 
good performance on that.   Is there some reason you don't want to?

Simon

From: glasgow-haskell-users-boun...@haskell.org 
[mailto:glasgow-haskell-users-boun...@haskell.org] On Behalf Of Greg Weber
Sent: 09 October 2011 17:39
To: GHC users
Subject: log time instead of linear for case matching

We have a couple use cases in Yesod that can potentially match many different 
patterns. Routing connects the url of an http request to a Haskell function. 
The current code just uses a pattern match, which scales linearly. So if a site 
has a hundred different routes (urls), it could take 100 comparisons to finally 
match the url to a function. Michael Snoyman is writing some code to make this 
issue obsolete. One of the things it does is use a Map lookup instead of a case 
match.

More worrying is our system for internationalization of a website. A user is 
supposed to make a sum type with every custom message as a constructor in that 
sum type.

data Msg = Model
 | Year
 | Please

-- Rendering function for English.
renderEnglish Model  = Model
renderEnglish Year   = Year
renderEnglish Please = Please fill in your car's details

-- Rendering function for Swedish.
renderSwedish Model  = Modell
renderSwedish Year   = Årgång
renderSwedish Please = Vänligen fyll i uppgifterna för din bil

So if there are 100 custom messages on a site, that will setup a case match 
with potentially 100 comparisons.

Note that we are using this technique for type safety- switching to a map here 
would be difficult. We want to know at compile time that a translation exists 
for every message.

So first of all I am wondering if a sum type comparison does in fact scale 
linearly or if there are optimizations in place to make the lookup constant or 
logarithmic. Second, I as wondering (for the routing case) if Haskell can make 
a string case comparison logarithmic so that users can use case comparisons 
instead of maps for string collections that are known at compile time and won't 
change.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: FW: Two Proposals

2011-10-05 Thread Simon Peyton-Jones
[adding ghc-users]

It's not easy, Phil.  Do you have any ideas?

For the 'then' case the name of the function serves as the verb.  One might say

then take 4
or
then takeWhile by salary  40

For grouping one might like to say the same  thing, such as
then groupBy by salary
but the typing rule is quite different, so we really need a different keyword.  
We chose the compound keyword then group to avoid needing a whole new keyword 
(group is treated specially only in tthis context). So you write
then group by salary using groupBy

Using this order of the pieces for the sorting case is harder. What would one 
say?  then process?  Like this?
then process by salary  40 using takeWhile
Not very nice.

One could use a new keyword for grouping theng say, thus:
theng groupBy by salary
But that is hardly beautiful either.

So the current story is not great, but it's the best I could think of. 
Improvements welcome.

Simon

|  -Original Message-
|  From: Philip Wadler [mailto:wad...@inf.ed.ac.uk]
|  Sent: 04 October 2011 18:15
|  To: Simon Peyton-Jones; George Giorgidze
|  Subject: Re: FW: Two Proposals
|  
|  George,
|  
|  Nice proposal.  I like the idea of symmetry, but don't at all like the
|  idea that f comes before e for 'then' but f comes after e for 'then
|  group'.  Can you rethink it and come up with something even more
|  symmetric?
|  
|  Yours,  -- P
|  
|  
|  On Tue, Oct 4, 2011 at 9:23 AM, Simon Peyton-Jones
|  simo...@microsoft.com wrote:
|   FYI
|  
|   -Original Message-
|   From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-
|  users-boun...@haskell.org] On Behalf Of George Giorgidze
|   Sent: 30 September 2011 18:28
|   To: glasgow-haskell-users@haskell.org
|   Subject: Two Proposals
|  
|   GHC Users,
|  
|   I would like to make to the following two proposals:
|    * Eliminate the default grouping close from SQL-like comprehensions
|    * Introduce a GHC extension for list literal overloading
|  
|   OK, let me start with the first proposal.
|  
|   Currently, the SQL-like comprehension notation (both in its list 
comprehension
|  and monad comprehension variants) features the following five clauses:
|  
|   then f
|   then f by e
|   then group by e
|   then group using f
|   then group by e using f
|  
|   The first two clauses are used for specifying transformations of type [a] 
- [a]
|  (or Monad m = m a- m a for monad comprehensions). The following three
|  clauses are used for specifying transformations of type [a] - [[a]] (or 
Monad m,
|  Functor f = m a - m (f a) for monad comprehensions). See [1] for further
|  details.
|  
|   Note that the third clause does not mention which function is used for 
grouping.
|  In this case GHC.Exts.groupWith function is used as a default for list
|  comprehensions and the mgroupWith function from the MonadGroup class is used
|  as a default for monad comprehensions.
|  
|   I would like to suggest to remove the third clause for the following 
reasons:
|   * Currently the syntax is asymmetrical. Note that there is the default 
case for
|  the 'then group' clause and not for the 'then' clause.
|   * In the current notation it is not clear which grouping function is used 
in the
|  default case
|   * For many monads including lists it is not clear which function should be
|  selected as a default (e.g., the groupWith function also does sorting and it 
is not
|  clear to me why this should be the default)
|   * Gets rid of the MonadGroup class. Currently the sole purpose of this 
class is to
|  introduce a default grouping function for monad comprehensions.
|   * Explicit mention of the grouping function would make  monad/list
|  comprehensions much easier to read by making it immediately apparent which
|  function is used for grouping.
|  
|   My second proposal is to introduce the OverloadedLists extension that 
overloads
|  list literals. See Section 5.2 in [1] for details.
|  
|   Basically the idea is to treat list literals like:
|  
|   [1,2,3]
|  
|   as
|  
|   fromList [1,2,3]
|  
|   where
|  
|   class IsList l where
|    type Item l
|    fromList :: [Item l] - l
|  
|   In the following I give useful instances of the IsList class.
|  
|   instance IsList [a] where
|    type Item [a] = a
|    fromList = id
|  
|   instance (Ord a) = IsList (Set a) where
|    type Item (Set a) = a
|    fromList = Set.fromList
|  
|   instance (Ord k) = IsList (Map k v) where
|    type Item (Map k v) = (k,v)
|    fromList = Map.fromList
|  
|   instance IsList (IntMap v) where
|    type Item (IntMap v) = (Int,v)
|    fromList = IntMap.fromList
|  
|   instance IsList Text where
|    type Item Text = Char
|    fromList = Text.pack
|  
|   As you can see the extension would allow list literals to be used for 
sets, maps
|  and integer maps. In addition the suggested OverloadedLists extension would
|  subsume OverloadedStrings extension (see the instance for Text, for example

RE: Two Proposals

2011-10-05 Thread Simon Peyton-Jones
|  In the spirit of don't let the perfect be the enemy of the good
|  though, I'm solidly in favor of the original proposal as it is. 

This is my thought too.  George is proposing to extend Haskell's existing 
mechanism for numeric literals (namely, replace 4 by (fromInteger 
(4::Integer))), so that it works for lists, just as Lennart did for Strings.  
One could do more, as Yitz has suggested, but that would be an altogether 
bigger deal, involving Template Haskell and quite a bit of new design; and if 
done should apply uniformly to numeric and string literals too. 

So personally I favour George's general approach as a first step.  But here is 
one thought.  In the spirit of monad comprehensions, should we not treat
[a,b,c]
as short for
return a `mappend` return b `mappend` return c
so that [a,b,c] syntax is, like [ e | x - xs ] syntax, just short for monadic 
goop.  Then we would not need a new class at all, which would be nice.

That isn't quite what Roman was suggesting (he wanted to supply the 'cons' and 
'nil') but it's closer, less head-biased, and it seems to fit the spirit of 
monad comprehensions.

I'm not sure if this plan would support [(fred,45), (bill,22)] :: Map 
String Int.  Probably not.   Maybe that's a shortcoming... but such Maps are a 
rather surprising use of list literals.  

Simon

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


RE: Unwanted eta-expansion

2011-10-04 Thread Simon Peyton-Jones
Combining lambdas makes a big difference in GHC. For example
f = \x. let y = E in \z. BODY
The function f takes one argument, and returns a heap-allocated lambda.  If E 
is cheap (say just a constructor) it might well be more efficient to transform 
to
f = \xz. let y = E in BODY

Pattern matching is another example, and GHC indeed eta expands through that by 
default, if it makes two lambdas into one.

To switch it off try -fno-do-lambda-eta-expansion.

Simon


| -Original Message-
| From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-users-
| boun...@haskell.org] On Behalf Of Roman Cheplyaka
| Sent: 04 October 2011 07:40
| To: glasgow-haskell-users@haskell.org
| Subject: Unwanted eta-expansion
| 
| Suppose I want a foldl which is evaluated many times on the same
| list but with different folding functions.
| 
| I would write something like this, to perform pattern-matching on the
| list only once:
| 
| module F where
| myFoldl :: [a] - (b - a - b) - b - b
| myFoldl [] = \f a - a
| myFoldl (x:xs) = let y = myFoldl xs in \f a - y f (f a x)
| 
| However, for some reason GHC eta-expands it back. Here's what I see in
| the core:
| 
|   % ghc -O2 -ddump-simpl -fforce-recomp -dsuppress-module-prefixes \
| -dsuppress-uniques -dsuppress-coercions F.hs
| 
|  Tidy Core 
| Rec {
| myFoldl [Occ=LoopBreaker]
|   :: forall a b. [a] - (b - a - b) - b - b
| [GblId, Arity=3, Caf=NoCafRefs, Str=DmdType SLL]
| myFoldl =
|   \ (@ a) (@ b) (ds :: [a]) (eta :: b - a - b) (eta1 :: b) -
| case ds of _ {
|   [] - eta1; : x xs - myFoldl @ a @ b xs eta (eta eta1 x)
| }
| end Rec }
| 
| Why does it happen and can it be suppressed?
| 
| This is GHC 7.0.4.
| 
| 
| --
| Roman I. Cheplyaka :: http://ro-che.info/
| 
| ___
| 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: mkTopLevEnv: not interpreted main:Main

2011-10-04 Thread Simon Peyton-Jones
| I will work on building a smaller complete test case that reproduces the
| issue, and I could have done a better job of at least pointing out the
| relevant code for you.  Sorry about that.

I'm afraid I still can't guess what's happening. It'd be really helpful if you 
could build a smaller test case.  

Are you using GHC HEAD (or at least 7.2?). There have been changes in this 
area, and I'm looking at the HEAD code.  So it's worth trying the latest 
version, lest we end up debugging something that is already fixed.

If you build the HEAD from source you can also look at the call to mkTopLevEnv 
and print out a bit more trace info to help narrow things down.

Sorry not to be more helpful.

Simon

| -Original Message-
| From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-users-
| boun...@haskell.org] On Behalf Of Chris Smith
| Sent: 03 October 2011 14:43
| To: Simon Peyton-Jones
| Cc: glasgow-haskell-users@haskell.org
| Subject: RE: mkTopLevEnv: not interpreted main:Main
| 
| Thanks, Simon.
| 
| I will work on building a smaller complete test case that reproduces the
| issue, and I could have done a better job of at least pointing out the
| relevant code for you.  Sorry about that.
| 
| I'm definitely not building my own IIModule.  The use of the GHC API is
| as follows.  (I'm fairly sure you can ignore doWithErrors, so I haven't
| included it; it just sets up some log actions and exception and signal
| handlers, runs its argument in the Ghc monad, and converts the result
| from a Maybe to an Either that reports errors).
| 
| doWithErrors :: GHC.Ghc (Maybe a) - IO (Either [String] a)
| 
| compile :: String - String - FilePath - IO (Either [String] t)
| compile vname tname fn = doWithErrors $ do
| dflags - GHC.getSessionDynFlags
| let dflags' = dflags {
| GHC.ghcMode = GHC.CompManager,
| GHC.ghcLink = GHC.LinkInMemory,
| GHC.hscTarget = GHC.HscAsm,
| GHC.optLevel = 2,
| GHC.safeHaskell = GHC.Sf_Safe,
| GHC.packageFlags = [GHC.TrustPackage gloss,
| GHC.ExposePackage gloss-web-adapters ]
| }
| GHC.setSessionDynFlags dflags'
| target - GHC.guessTarget fn Nothing
| GHC.setTargets [target]
| r - fmap GHC.succeeded (GHC.load GHC.LoadAllTargets)
| case r of
| True - do
| mods - GHC.getModuleGraph
| let mainMod = GHC.ms_mod (head mods)
| GHC.setContext [ mainMod ]
|[ GHC.simpleImportDecl
|(GHC.mkModuleName Graphics.Gloss),
|  GHC.simpleImportDecl
|(GHC.mkModuleName GlossAdapters) ]
| v - GHC.compileExpr $ vname ++  ::  ++ tname
| return (Just (unsafeCoerce# v))
| False - return Nothing
| 
| --
| Chris
| 
| 
| ___
| 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: Two Proposals

2011-10-04 Thread Simon Peyton-Jones
I like both George's proposals.

Simon

| -Original Message-
| From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-users-
| boun...@haskell.org] On Behalf Of George Giorgidze
| Sent: 30 September 2011 18:28
| To: glasgow-haskell-users@haskell.org
| Subject: Two Proposals
| 
| GHC Users,
| 
| I would like to make to the following two proposals:
|   * Eliminate the default grouping close from SQL-like comprehensions
|   * Introduce a GHC extension for list literal overloading
| 
| OK, let me start with the first proposal.
| 
| Currently, the SQL-like comprehension notation (both in its list 
comprehension and
| monad comprehension variants) features the following five clauses:
| 
| then f
| then f by e
| then group by e
| then group using f
| then group by e using f
| 
| The first two clauses are used for specifying transformations of type [a] - 
[a] (or
| Monad m = m a- m a for monad comprehensions). The following three clauses 
are used
| for specifying transformations of type [a] - [[a]] (or Monad m, Functor f = 
m a -
| m (f a) for monad comprehensions). See [1] for further details.
| 
| Note that the third clause does not mention which function is used for 
grouping. In
| this case GHC.Exts.groupWith function is used as a default for list 
comprehensions
| and the mgroupWith function from the MonadGroup class is used as a default 
for monad
| comprehensions.
| 
| I would like to suggest to remove the third clause for the following reasons:
| * Currently the syntax is asymmetrical. Note that there is the default case 
for the
| 'then group' clause and not for the 'then' clause.
| * In the current notation it is not clear which grouping function is used in 
the
| default case
| * For many monads including lists it is not clear which function should be 
selected
| as a default (e.g., the groupWith function also does sorting and it is not 
clear to
| me why this should be the default)
| * Gets rid of the MonadGroup class. Currently the sole purpose of this class 
is to
| introduce a default grouping function for monad comprehensions.
| * Explicit mention of the grouping function would make  monad/list 
comprehensions
| much easier to read by making it immediately apparent which function is used 
for
| grouping.
| 
| My second proposal is to introduce the OverloadedLists extension that 
overloads list
| literals. See Section 5.2 in [1] for details.
| 
| Basically the idea is to treat list literals like:
| 
| [1,2,3]
| 
| as
| 
| fromList [1,2,3]
| 
| where
| 
| class IsList l where
|   type Item l
|   fromList :: [Item l] - l
| 
| In the following I give useful instances of the IsList class.
| 
| instance IsList [a] where
|   type Item [a] = a
|   fromList = id
| 
| instance (Ord a) = IsList (Set a) where
|   type Item (Set a) = a
|   fromList = Set.fromList
| 
| instance (Ord k) = IsList (Map k v) where
|   type Item (Map k v) = (k,v)
|   fromList = Map.fromList
| 
| instance IsList (IntMap v) where
|   type Item (IntMap v) = (Int,v)
|   fromList = IntMap.fromList
| 
| instance IsList Text where
|   type Item Text = Char
|   fromList = Text.pack
| 
| As you can see the extension would allow list literals to be used for sets, 
maps and
| integer maps. In addition the suggested OverloadedLists extension would 
subsume
| OverloadedStrings extension (see the instance for Text, for example). Having 
said
| that, for now, I am not suggesting to remove the OverloadedStrings extension 
as it
| appears to be widely used.
| 
| This extension could also be used for giving data-parallel array literals 
instead of
| the special syntax used currently.
| 
| Unless there is a vocal opposition to the aforementioned two proposals, I 
would like
| to implement them in GHC. Both changes appear to be straightforward to 
implement.
| 
| Thanks in advance for your feedback.
| 
| Cheers, George
| 
| [1] http://www-db.informatik.uni-tuebingen.de/files/giorgidze/haskell2011.pdf
| ___
| 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: mkTopLevEnv: not interpreted main:Main

2011-10-03 Thread Simon Peyton-Jones
I don't have a good answer here.  FWIW

* I believe that the only call to mkTopLevEnv is in 
InteractiveEval.findGlobalRdrEnv,
  which in turn only calls mkTopLev on imports which are specified by an 
IIModule
  specification (see HscTypes.InteractiveImport).

* I think that IIModule things should always be interpreted modules
  else we don't *know* their full top-level environment

* I can't account for how you are getting an IIModule of your main:MyModule,
  because all the places that create IIModule specs check that the module
  is interpreted. Could you be creating that IIModule yourself?  (If so use
  IIDecl instead.)

It's hard to say more without a reproducible test case -- and I'm not too keen 
on trying to build your entire project unless there is no alternative -- 
usually there are lots of other dependencies.

maybe others have ideas too.

Simon

| -Original Message-
| From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-users-
| boun...@haskell.org] On Behalf Of Chris Smith
| Sent: 02 October 2011 05:59
| To: glasgow-haskell-users@haskell.org
| Subject: mkTopLevEnv: not interpreted main:Main
| 
| So I'm trying to fix a bug in a web application that's using the GHC API
| with GHC 7.2.  If it helps, the application is gloss-web, source code at
| https://github.com/cdsmith/gloss-web and the relevant module is
| src/Source.hs.
| 
| The error I'm getting is
| 
| no location info: mkTopLevEnv: not interpreted main:MyModule
| 
| I get this occasionally when two pieces of source code happen to get
| compiled at approximately the same time, but most of the time everything
| works fine.  The module name there is whichever one I've defined in the
| source code I'm compiling.  It's correct that the module is not
| interpreted; I'm specifying options
| 
| hscTarget = HscAsm
| ghcLink = LinkInMemory
| 
| But it's unclear to me why GHC occasionally decides to require that it
| be interpreted and complain, when compiling the code works fine in any
| other circumstance.  Anyone else seen anything like this, or know what
| the cause is?
| 
| A few notes:
| 
| 1. It doesn't appear to be a straight-forward reentrancy issue, as
| wrapping uses of the GHC API with an MVar lock doesn't affect it at all.
| However, it definitely *is* correlated with multiple compiles at
| approximately the same time.  Very odd there.
| 
| 2. On a whim, I tried adding a performGC before and after each use of
| the compiler to try to isolate the uses of the GHC API more completely.
| Oddly enough, a performGC before the compile makes the problem much
| WORSE.  I found that interesting; maybe it's a hint.
| 
| 3. If you want to build my code and reproduce it, the easiest way is to
| comment out line 110 (keepAlive cmap digest 30) of src/Source.hs.  Doing
| so will break the bit that caches recently compiled source code, making
| it much easier to actually call the GHC API several times in rapid
| succession just by rapidly clicking the Run button in the web app.
| 
| If there's anything I can do to get more information, I'm happy to do so
| as well.  I'm not terribly familiar with the flags or options for GHC,
| as I've never done this before.
| 
| --
| Chris Smith
| 
| 
| 
| ___
| 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: Proposal: Add default instances for Functor and Applicative

2011-09-24 Thread Simon Peyton-Jones
|  With regard to [1], default superclass instances, is there already a plan to 
| implement them? And if so, when is it expected to be finished? 
|
|  [1] http://hackage.haskell.org/trac/ghc/wiki/DefaultSuperclassInstances

It definitely won't be in 7.4 I'm afraid.  

One thing that would be motivating would be a list of people who actively want 
default superclass instances and why you want them.  My own priorities for 
implementing stuff are much influenced by what GHC's users seem to value.  I've 
added an Applications section to [1]; do add yourself and sketch how you'd 
use the new feature.

Simon


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


RE: Evaluating type expressions in GHCi

2011-09-23 Thread Simon Peyton-Jones
Yes, it expands type synonyms too

S

From: sean.leat...@gmail.com [mailto:sean.leat...@gmail.com] On Behalf Of Sean 
Leather
Sent: 23 September 2011 13:43
To: Simon Peyton-Jones
Cc: GHC Users List
Subject: Re: Evaluating type expressions in GHCi

Hi Simon,

*TF :kind F Int
F Int :: *
*TF :kind! F Int
F Int :: *
  = Bool

Does this also work with plain ol' type synonyms? I just noticed that the :t 
undefined :: T trick doesn't seem to work with type synonyms.

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


RE: Evaluating type expressions in GHCi

2011-09-20 Thread Simon Peyton-Jones
Sean

Yes, this has been asked for before, and it wouldn't be hard to implement.


What should the GHCi command be *called*?

We already have :kind, which displays the kind of a type.  Maybe :kind! should 
evaluate the type as well?  Or perhaps :kind should evaluate anyway (although 
that would be a bit  inconsistent with :type which does not evaluate the 
expression)

Or :normtype?   short for normalise type

Simon

From: glasgow-haskell-users-boun...@haskell.org 
[mailto:glasgow-haskell-users-boun...@haskell.org] On Behalf Of Sean Leather
Sent: 20 September 2011 11:34
To: GHC Users List
Subject: Evaluating type expressions in GHCi

I would like to ask GHCi for the type that a type expression will evaluate to, 
once all definitions of type synonyms and (when possible) type families have 
been inlined.

It appears that I can do some part of this for type T by using :t undefined :: 
T:

type family F a
type instance F Int = Bool
type instance F Bool = Int
type instance F (a, b) = (F a, F b)

ghci :t undefined :: F (Int, Bool)
undefined :: F (Int, Bool) :: (Bool, Int)

I also get what I expect here:

ghci :t undefined :: F (a, Bool)
undefined :: F (a, Bool) :: (F a, Int)

Of course, this doesn't work on types of kinds other than *.

Is it possible and worth having another GHCi command to perform this operation 
for any types? It could be the type analogue to :t such that it evaluates the 
type and gives its kind.

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


RE: accessing compilation parameters from template haskell

2011-09-16 Thread Simon Peyton-Jones
The difficulty here is that the TH library, by design, doesn't depend on GHC.  
So we can't have a TH function
getFlags :: Q DynFlags
or (as you suggest, more or less)
runTc :: TcM a - Q a
because to write those type signatures in Language.Haskell.TH.Syntax you'd need 
to import GHC.

There's no difficulty in *practice*!  Q more or less *is* TcM.

Still I don't really know how to get around this in a beautiful way.

Simon

| -Original Message-
| From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-users-
| boun...@haskell.org] On Behalf Of Ganesh Sittampalam
| Sent: 16 September 2011 06:42
| To: GHC users
| Subject: accessing compilation parameters from template haskell
| 
| Hi,
| 
| It would be useful to access the current compilation parameters or even
| an entire RunGhc monad from inside a Template Haskell splice. Is there
| any way to do this?
| 
| The reason I want to do this is I'm using the ghc API at runtime to
| dynamically execute code, and I want both the dynamically loaded code
| and static code to use a shared runtime module that defines some types
| used for communication across the boundary. To guarantee the internal
| representations etc are the same, I store the object file of the runtime
| during compilation then load it dynamically at runtime - but to make
| this work I need to know where the object file is (-odir and -hidir) and
| I also need to know or be able to deduce the GHC DynFlags so I can
| replicate them at runtime.
| 
| I could also achieve this goal by putting my runtime in a separate
| package and installing it first, but that's less self-contained and
| would be a pain during development.
| 
| 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: Windows build problems

2011-09-16 Thread Simon Peyton-Jones
|  If you get it to work, I'd appreciate detailed (Windows is so far utterly
|  incomprehensible to me, so they'd better be very explicit) instructions.
| 
| 
| I feel your pain. The Windows instructions could definately use some
| updating. :)
| 
| I ended up getting an error during stage 2 about the iconv.dll not
| being findable. (I'm guessing the new msys/mingw autosmarted GHC
| boot/configure or cabal configure process somehow )

If one of you felt able to update the instructions (it's a wiki), when you've 
figured out what to do, that would be absolutely fantastic!

Thanks

Simon

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


RE: accessing compilation parameters from template haskell

2011-09-16 Thread Simon Peyton-Jones
| Would making a template-haskell-ghc package make sense? Might be
| overkill just for my requirement but there could be other things like
| support for GHC-specific language extensions that might also logically
| belong there.

I don't know --  I don't know what it would look like. By all means have a go!

S
| 
| On 16/09/2011 08:21, Simon Peyton-Jones wrote:
|  The difficulty here is that the TH library, by design, doesn't depend on 
GHC.  So
| we can't have a TH function
|  getFlags :: Q DynFlags
|  or (as you suggest, more or less)
|  runTc :: TcM a - Q a
|  because to write those type signatures in Language.Haskell.TH.Syntax you'd 
need to
| import GHC.
| 
|  There's no difficulty in *practice*!  Q more or less *is* TcM.
| 
|  Still I don't really know how to get around this in a beautiful way.
| 
|  Simon
| 
|  | -Original Message-
|  | From: glasgow-haskell-users-boun...@haskell.org 
[mailto:glasgow-haskell-users-
|  | boun...@haskell.org] On Behalf Of Ganesh Sittampalam
|  | Sent: 16 September 2011 06:42
|  | To: GHC users
|  | Subject: accessing compilation parameters from template haskell
|  |
|  | Hi,
|  |
|  | It would be useful to access the current compilation parameters or even
|  | an entire RunGhc monad from inside a Template Haskell splice. Is there
|  | any way to do this?
|  |
|  | The reason I want to do this is I'm using the ghc API at runtime to
|  | dynamically execute code, and I want both the dynamically loaded code
|  | and static code to use a shared runtime module that defines some types
|  | used for communication across the boundary. To guarantee the internal
|  | representations etc are the same, I store the object file of the runtime
|  | during compilation then load it dynamically at runtime - but to make
|  | this work I need to know where the object file is (-odir and -hidir) and
|  | I also need to know or be able to deduce the GHC DynFlags so I can
|  | replicate them at runtime.
|  |
|  | I could also achieve this goal by putting my runtime in a separate
|  | package and installing it first, but that's less self-contained and
|  | would be a pain during development.
|  |
|  | 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


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


Records in Haskell

2011-09-15 Thread Simon Peyton-Jones
Friends

Provoked the (very constructive) Yesod blog post on Limitations of Haskell, 
and the follow up discussion, I've started a wiki page to collect whatever 
ideas we have about the name spacing issue for record fields.

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

As Simon M said on Reddit, this is something we'd like to fix; but we need a 
consensus on how to fix it.

Simon


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


RE: Records in Haskell

2011-09-15 Thread Simon Peyton-Jones
J Garrett Morris asked me

| I also rather like the TDNR proposal, as it's rather similar to the
| approach we're taking in Habit (our pet language at Portland State).
| However, I'm curious as to why you don't want to quantify over name
| resolution constraints.  For example, why shouldn't:
| 
| x f = f.x
| 
| be a reasonable function? 

Yes, it would, and of course any impl of TDNR would need an internal constraint 
similar to your Select.  In my original proposal I was hiding that, but it has 
to be there in the implementation.  But you are right that making it explicit 
might be a good thing.  Esp with Julien's new kind stuff (coming soon) we 
should be able to say

class Select (rec :: *) (fld :: String) where
  type ResTy rec fld:: *
  get :: rec - ResTy rec fld

data T = MkT { x,y :: Int }
instance Select T x where
  get (MkT {x = v}) = v

And now we desugar   
f.x
as
get @T @x f

where the @ stuff is type application, because get's type is ambiguous:
get :: forall rec fld. Select rec fld = rec - ResTy rec fld

Just like what Hobbit does really.

You probably don't use the idea of extending to arbitrary other functions do 
you?  (Which Ian does not like anyway.)  Something like

getIndex :: T - Int
getIndex (MkT x y) = x+y

Then I'd like to be able to say

t.getIndex

So there's an implicit instance
instance Select T getIndex where
 type ResTy T getIndex = Int
 get = getIndex


It's a little unclear what operations should be in class Select.  'get' 
certainly, but I propose *not* set, because it doesn't make sense for getIndex 
and friends.  So that would mean you could write a polymorphic update:

f v = f { x = v }

Restricting to record fields only would, I suppose, allow polymorphic update, 
by adding a 'set' method to Select.

Simon

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


RE: [Template-haskell] change in [d| |] and creating instances in template-haskell 2.7

2011-09-08 Thread Simon Peyton-Jones
| Yeah. I would expect this to work:
| 
| inferBar2 :: Name - Q [Dec]
| inferBar2 typeName =
|[d| instance Bar $(conT typeName) where
|  bar _ = sucker
|  |]
| 
| But I get the same error:
| 
|  inferBar2 'Bool
|==
|  show-test.hs:4:3-18
|  instance Bar Bool where
|  { bar_aTK _ = sucker }

Yes that should work. And it does with HEAD.  I fixed a bunch of stuff in the 
ticket I cited.  Maybe try a snapshot distribution?

Simon

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


RE: Superclass defaults

2011-09-02 Thread Simon Peyton-Jones
Too many words!  I'm losing track.  What I'm proposing is Option 2 under The 
design of the opt-out mechanism on 
http://hackage.haskell.org/trac/ghc/wiki/DefaultSuperclassInstances

I believe that meets everyone's goals:
  * A warning encourages you to fix the client code
  * But you can turn it off, and it's not fatal.

Does anyone advocate something else?

Simon

| -Original Message-
| From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-users-
| boun...@haskell.org] On Behalf Of Jonas Almström Duregård
| Sent: 02 September 2011 16:50
| To: Conor McBride
| Cc: GHC users
| Subject: Re: Superclass defaults
| 
|  The question then comes down to whether that warning should ever be
|  strengthened to an error.
| 
| Indeed.
| 
|  I agree that such a scenario is possible. The present situation gives
|  no choice but to do things badly, but things often get done badly the
|  first time around anyway. Perhaps I'm just grumpy, but I think we
|  should aim to make bad practice erroneous where practicable. Once
|  the mistake is no longer forced upon us, it becomes a mistake that
|  deserves its penalty in labour. Silent pre-emption is bad practice and
|  code which relies on it should be fixed: it's not good to misconstrue
|  an instance declaration because you don't know which instance
|  declarations are somewhere else. Nonmonotonic reasoning is always a
|  bit scary.
| 
|  From a library design perspective, we should certainly try to get these
|  hierarchical choices right when we add classes. I accept that it should
|  be cheap to fix mistakes (especially when the mistake is lack of
|  foresight. Sticking with the warning rather than the error reduces the
|  price of this particular legacy fix at the cost of tolerating misleading
|  code. I agree that the balance of this trade-off is with the warning,
|  for the moment, but I expect it to shift over time towards the error.
|  But if it's clear what the issue is, then we can at least keep it under
|  review.
| 
| I agree. Making bad practice erroneous is good, but its not really the
| bad practice that raises the error here. You have no serious problems
| until you try to change your bad design to a good one. Like you say it
| should be cheap to fix mistakes.
| 
|  Will there be a solution to this dilemma that I have missed? Should
|  the client code be allowed opt-out from the superclass preemptively
|  before it is given a default? Won't that cause a similar perplexity?
| 
|  I don't know what you mean by this. Perhaps you could expand on it?
| 
| What I'm trying to ask is if you can write compatible code that will
| work across gradual changes of the compiler and the libraries.
| 
| Suppose we have library with class C. In a newer version of the
| library we add an intrinsic superclass S. Also suppose the compiler
| implements option 1. Now the users of the library want to write code
| that uses both C and S, and that's compatible with both the new and
| the old library. From what I can tell there are three situations that
| needs to be covered:
| 
| 1) Old compiler - Old library
| Here we need to specify both instances, and we cant hide the default S
| instance because its not supported by the compiler. This also applies
| for other situations where the client must use Haskell 2010 compatible
| code.
| 
| 2) New compiler - Old library
| Here we also need to specify both instances.
| 
| 3) New compiler - New library
| We can either write both instances and hide the default or we can just
| write an instance for C.
| 
| Clearly code that covers situation 1 will never be compatible with situation 
3.
| 
| The question I was asking was if we are allowed to hide the default
| instance of S in situation 2. In that case you can write compatible
| code for situation 2 and 3. The possible confusion from this is that
| you hide a default implementation thats not defined. Maybe it's not as
| bad as overriding silently, but there is some room for error where you
| think you have blocked a superclass instance but really you have just
| blocked some completely unrelated class.
| 
| Of course we can get compatibility across all three using CPP but I
| really wish we won't need that.
| 
| As time passes, situation 1 will become more rare, although situation
| 2 and 3 can reoccur endlessly as new libraries are designed and
| redesigned.
| 
| Regards,
| Jonas
| 
| ___
| 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: Superclass defaults

2011-08-31 Thread Simon Peyton-Jones
|  Won't option 1 Reject this as a duplicate instance declaration, which
|  indeed it is. conflict with design goal 1: a class C can be
|  re-factored into a class C with a superclass S, without disturbing any
|  clients?   

Yes, option 1 does conflict with design goal 1; good point.  There seems to be 
a lot of support for Option 3... but what about Option 2 (ie pre-empt but give 
a warning)?

I've updated the wiki page 
http://hackage.haskell.org/trac/ghc/wiki/DefaultSuperclassInstances to reflect 
this discussion.

Simon


| -Original Message-
| From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-users-
| boun...@haskell.org] On Behalf Of Sebastian Fischer
| Sent: 30 August 2011 03:49
| To: Bas van Dijk
| Cc: glasgow-haskell-users@haskell.org; Simon Peyton-Jones
| Subject: Re: Superclass defaults
| 
| On Mon, Aug 29, 2011 at 6:21 AM, Bas van Dijk v.dijk@gmail.com wrote:
| 
|  Won't option 1 Reject this as a duplicate instance declaration, which
|  indeed it is. conflict with design goal 1: a class C can be
|  re-factored into a class C with a superclass S, without disturbing any
|  clients?   
| 
| If yes, I prefer option 3:
| 
|  Allow the explicit to supersede the intrinsic default silently.
| 
| The argument against this option is:
| 
|  I might notice
|  that Foo is a monad and add a Monad Foo instance in my own code,
|  expecting the Applicative Foo instance to be generated in concert; to
|  my horror, I find my code has subtle bugs because the package
|  introduced a different, non-monadic, Applicative Foo instance which
|  I'm accidentally using instead.
| 
| This seems rare enough that it's feasible to issue a warning if a
| default instance is overwritten by an explicit instance in a different
| module which would prevent the described perplexity. This wouldn't,
| for example, disturb the transformers example mentioned by Bas because
| (I think) all instances are defined in the same module.
| 
| Sebastian
| 
| ___
| 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: Panic when using syb with GHC API

2011-08-26 Thread Simon Peyton-Jones
Feel free to propose better solutions.

The underlying issue is that before type checking GHC (obviously) doesn't know 
the types of things, while afterwards it does.  The whole HsSyn tree is 
parameterised over the types of identifiers:

  Parsed:   HsExpr RdrNames
  Renamed:  HsExpr Name
  Typechecked:  HsExpr Id

One alternative would be to parameterise the tree over the type of 
type-decorations, so instead of 'PostTcType' you'd have 'ty' (a variable) 
instead.  So we'd have

  Renamed: HsExpr Name ()
  Typechecked: HsExpr Id   Type

To me this seems like a bit of a sledgehammer to crack a nut; and I think there 
are a couple of other similar things (like SyntaxExpr).  But it might be 
possible.

Another possibility would be for those PostTcTypes to be (Maybe Type), which 
would be less convenient when you know they are there.

Simon

| -Original Message-
| From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-users-
| boun...@haskell.org] On Behalf Of Ranjit Jhala
| Sent: 25 August 2011 22:47
| To: Thomas Schilling
| Cc: glasgow-haskell-users@haskell.org
| Subject: Re: Panic when using syb with GHC API
| 
| Hi,
| 
| I ran into a similar issue earlier -- you might also look at this
| 
|   http://mistuke.wordpress.com/category/vsx/
| 
| (also linked from http://haskell.org/haskellwiki/GHC/As_a_library#Links)
| 
| Hope to elaborate the text there one of these days...
| 
| Ranjit.
| 
| 
| On Aug 25, 2011, at 2:22 AM, Thomas Schilling wrote:
| 
|  GHC's parse tree contains lots of placeholders.  You are not supposed
|  to look at them until a specific phase has been run.  For example,
|  anything of type SyntaxExpr is an error thunk until the renamer has
|  been run.  Unfortunately, SyntaxExpr is just a type synonym, so
|  there's no way to distinguish them via SYB.
| 
|  The simplest workaround is to adapt the default traversal code for the
|  nodes which may contain such error thunks.  A better solution would be
|  to change the GHC AST to wrap such possibly undefined nodes with
|  newtypes, but that would only take effect once the next version of GHC
|  is released.
| 
|  On 24 August 2011 23:11, Simon Hengel simon.hen...@wiktory.org wrote:
|  Hello,
|  I'm trying to query a type-checked module with syb, this works for a
|  plain binding.  But as soon as I add a type signature for that binding,
|  I get an panic!
| 
|  I experienced similar problems with a renamed module.
| 
|  Are those data structures meant to be used with syb?  And if yes, what
|  did I miss?
| 
|  Bellow is some code to reproduce my issue.  Any help is very much
|  appreciated.
| 
| -- A.hs
| module Main where
| 
| import GHC
| import Outputable
| import Data.Generics
| import GHC.Paths (libdir)
| 
| import Bag
| 
| main :: IO ()
| main = do
|   m - parse
|   putStrLn $ showSDoc $ ppr $ m
|   putStrLn \n---\n
|   putStrLn $ showSDoc $ ppr $ selectAbsBinds m
| 
| parse = runGhc (Just libdir) $ do
|   _ - getSessionDynFlags = setSessionDynFlags
|   target - guessTarget B.hs Nothing
|   setTargets [target]
|   Succeeded - load LoadAllTargets
|   modSum - getModSummary $ mkModuleName B
|   m - parseModule modSum = typecheckModule
|   return $ typecheckedSource m
| 
| selectAbsBinds :: GenericQ [HsBindLR Id Id]
| selectAbsBinds = everything (++) ([] `mkQ` f)
|   where
| f x@(AbsBinds _ _ _ _ _) = [x]
| f _ = []
| 
| 
| -- B.hs
| module B where
| 
| foo :: Char
| foo = 'f'
| 
|  Cheers,
|  Simon
| 
|  ___
|  Glasgow-haskell-users mailing list
|  Glasgow-haskell-users@haskell.org
|  http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
| 
| 
| 
| 
|  --
|  Push the envelope. Watch it bend.
| 
|  ___
|  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


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


RE: Superclass defaults

2011-08-22 Thread Simon Peyton-Jones
|  I don't completely understant how does it work. Does client need to enable
|  language extension to get default instances?
| 
| I think that the extension would only be required to *define them*,
| not for them to be generated. The more conservative choice would
| indeed be to require the extension for both, though.

Yes. I've clarified 
http://hackage.haskell.org/trac/ghc/wiki/DefaultSuperclassInstances to say this.

|  Also proposal cannot fix Functor/Applicative/Monad problem without breaking
|  client code. It requires explicit opt-out but client may define Applicative
|  instance. And unless hiding is added it will result in compile error.
| 
| I think the intention (at least as I understand it) is that a
| superclass default is only used to generate an instance if there is
| not already some suitable instance in scope, just like a default
| method is only used if there is not some explicit definition for the
| method in the instance. 

Actually that is not what Conor and I proposed.  See 
http://hackage.haskell.org/trac/ghc/wiki/DefaultSuperclassInstances.  Under 
Variations we discuss the silent-opt-out choice.  But it's bad enough 
knowing exactly what instances are in scope (given that they are not named), 
let alone having that control what further instances are or are not generated!  
For superclass defaults there is no such ambiguity.

Simon


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


RE: Can't find interface-file declaration for type constructor or class integer-gmp:GHC.Integer.Type.Integer

2011-08-18 Thread Simon Peyton-Jones
My guess is that you have not updated compiler/prelude/PrelNames, which 
contains wired-in knowledge of which modules certain functions and data types 
live in.  Check the ones you've moved!

S

| -Original Message-
| From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-users-
| boun...@haskell.org] On Behalf Of Johan Tibell
| Sent: 18 August 2011 15:45
| To: glasgow-haskell-users
| Subject: Can't find interface-file declaration for type constructor or class 
integer-
| gmp:GHC.Integer.Type.Integer
| 
| I'm trying to refactor the integer-gmp package to fix the breakage
| explained in #5384. During the refactoring I
| 
| * moved GHC.Integer.Type to GHC.Integer.GMP.Type, and
| * added a new GHC.Integer.Type module that re-exports parts of the
| interface now exposed by GHC.Integer.GMP.Type
| 
| The content of GHC.Integer.Type is just:
| 
| {-# LANGUAGE NoImplicitPrelude #-}
| {-# OPTIONS_HADDOCK hide #-}
| 
| -- If you change the module name or the export list you must update
| -- compiler/prelude/PrelNames.lhs.
| module GHC.Integer.Type (
|   Integer(..)
| , plusInteger
| , timesInteger
| , smallInteger
| , integerToWord
| , integerToInt
| , minusInteger
| , negateInteger
| , eqInteger
| , neqInteger
| , absInteger
| , signumInteger
| , leInteger
| , gtInteger
| , ltInteger
| , geInteger
| , compareInteger
| , gcdInteger
| , lcmInteger
| , andInteger
| , orInteger
| , xorInteger
| , complementInteger
| , shiftLInteger
| , shiftRInteger
| ) where
| 
| import GHC.Integer.GMP.Type
| 
| GHC doesn't seem to like this at all. It can no longer find the
| GHC.Integer.Type.Integer type:
| 
| $ inplace/bin/ghc-stage1   -H64m -O -fasm-package-name
| base-4.4.0.0 -hide-all-packages -i -ilibraries/base/.
| -ilibraries/base/dist-install/build
| -ilibraries/base/dist-install/build/autogen
| -Ilibraries/base/dist-install/build
| -Ilibraries/base/dist-install/build/autogen -Ilibraries/base/include
| -optP-DOPTIMISE_INTEGER_GCD_LCM -optP-include
| -optPlibraries/base/dist-install/build/autogen/cabal_macros.h -package
| ghc-prim-0.2.0.0 -package integer-gmp-0.3.0.0 -package rts-1.0
| -package-name base -XHaskell98 -XCPP -O -dcore-lint
| -no-user-package-conf -rtsopts -odir
| libraries/base/dist-install/build -hidir
| libraries/base/dist-install/build -stubdir
| libraries/base/dist-install/build -hisuf hi -osuf  o -hcsuf hc -c
| libraries/base/./Data/Maybe.hs -o
| libraries/base/dist-install/build/Data/Maybe.o
| 
| libraries/base/Data/Maybe.hs:70:13:
| Can't find interface-file declaration for type constructor or
| class integer-gmp:GHC.Integer.Type.Integer
|   Probable cause: bug in .hi-boot file, or inconsistent .hi file
|   Use -ddump-if-trace to get an idea of which file caused the error
| When deriving the instance for (Eq (Maybe a))
| 
| Here's the -ddump-if-trace log:
| 
| $ inplace/bin/ghc-stage1   -H64m -O -fasm-package-name
| base-4.4.0.0 -hide-all-packages -i -ilibraries/base/.
| -ilibraries/base/dist-install/build
| -ilibraries/base/dist-install/build/autogen
| -Ilibraries/base/dist-install/build
| -Ilibraries/base/dist-install/build/autogen -Ilibraries/base/include
| -optP-DOPTIMISE_INTEGER_GCD_LCM -optP-include
| -optPlibraries/base/dist-install/build/autogen/cabal_macros.h -package
| ghc-prim-0.2.0.0 -package integer-gmp-0.3.0.0 -package rts-1.0
| -package-name base -XHaskell98 -XCPP -O -dcore-lint
| -no-user-package-conf -rtsopts -odir
| libraries/base/dist-install/build -hidir
| libraries/base/dist-install/build -stubdir
| libraries/base/dist-install/build -hisuf hi -osuf  o -hcsuf hc -c
| libraries/base/./Data/Maybe.hs -o
| libraries/base/dist-install/build/Data/Maybe.o -ddump-if-trace
| FYI: cannont read old interface file:
| libraries/base/dist-install/build/Data/Maybe.hi: openBinaryFile:
| does not exist (No such file or directory)
| Considering whether to load base:GHC.Base
| Reading interface for base:GHC.Base;
| reason: GHC.Base is directly imported
| readIFace libraries/base/dist-install/build/GHC/Base.hi
| updating EPS_
| Considering whether to load ghc-prim:GHC.Generics
| Reading interface for ghc-prim:GHC.Generics;
| reason: GHC.Generics is directly imported
| readIFace /usr/local/google/src/ghc/libraries/ghc-prim/dist-
| install/build/GHC/Generics.hi
| updating EPS_
| updating EPS_
| Considering whether to load base:GHC.Base {- SYSTEM -}
| loadHiBootInterface base:Data.Maybe
| Considering whether to load ghc-prim:GHC.Types {- SYSTEM -}
| Reading interface for ghc-prim:GHC.Types;
| reason: Checking fixity for :
| readIFace /usr/local/google/src/ghc/libraries/ghc-prim/dist-
| install/build/GHC/Types.hi
| updating EPS_
| Considering whether to load ghc-prim:GHC.Types {- SYSTEM -}
| Considering whether to load ghc-prim:GHC.Types {- SYSTEM -}
| Starting fork { Declaration for Monad
| Loading decl for GHC.Base.Monad
| updating 

RE: Can't find interface-file declaration for type constructor or class integer-gmp:GHC.Integer.Type.Integer

2011-08-18 Thread Simon Peyton-Jones
| I shouldn't have to modify PrelNames since I kept GHC.Integer.Type,
| no? Or does PrelNames have to contain the name of the module that
| originally defined the type? 

Yes, exactly!

Simon


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


RE: Can't find interface-file declaration for type constructor or class integer-gmp:GHC.Integer.Type.Integer

2011-08-18 Thread Simon Peyton-Jones
It's hard to know what Ian had in mind, but I'm sure he'll tell us when he gets 
back from holiday.

Meanwhile, yes, it is hard to reconcile
* The wish to have multiple implementations of Integer
* The wired-in knowledge that GHC has
* The desire to have optimising rewrite rules in client libraries

I suggested one approach in the ticket earlier today; there might be others.  
It might be good to figure out a good design before going much further into 
implementation.

Simon

|  -Original Message-
|  From: Johan Tibell [mailto:johan.tib...@gmail.com]
|  Sent: 18 August 2011 18:14
|  To: Simon Peyton-Jones
|  Cc: glasgow-haskell-users
|  Subject: Re: Can't find interface-file declaration for type constructor or 
class
|  integer-gmp:GHC.Integer.Type.Integer
|  
|  On Thu, Aug 18, 2011 at 7:07 PM, Simon Peyton-Jones
|  simo...@microsoft.com wrote:
|   | I shouldn't have to modify PrelNames since I kept GHC.Integer.Type,
|   | no? Or does PrelNames have to contain the name of the module that
|   | originally defined the type?
|  
|   Yes, exactly!
|  
|  This causes some trouble though, as the module named in PrelNames must
|  exist in both in integer-gmp and integer-simple i.e. it must be some
|  generic name like GHC.Integer.Type rather than a name containing e.g.
|  GMP. I could keep the data type definition where it is
|  (GHC.Integer.Type) but then I would have a hard time exporting it from
|  e.g. GHC.Integer.GMP.Internals without undoing Ian's patch which
|  removed the slightly odd GHC.Integer - GHC.Integer.GMP.Internals -
|  GHC.Integer.Type module dependency in integer-gmp.


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


RE: Type families difference between 7.0.4 and 7.2.1

2011-08-17 Thread Simon Peyton-Jones
It's wrong. Thank you for pointing this out. I'll investigate.

Simon

| -Original Message-
| From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-users-
| boun...@haskell.org] On Behalf Of Luite Stegeman
| Sent: 16 August 2011 16:57
| To: glasgow-haskell-users@haskell.org
| Subject: Re: Type families difference between 7.0.4 and 7.2.1
| 
| sorry, I accidentally sent my reply to Brandon to the wrong address,
| not this list.
| 
| On Tue, Aug 16, 2011 at 4:56 PM, Dan Doel dan.d...@gmail.com wrote:
| ...
|  I don't really understand why it would be impossible not to export a
|  data family, given that (instances I understand). And of course, you
|  can selectively export methods of a class, so why not associated
|  types?
| 
| I don't understand that either. A link to the original discussion or
| issue number would be welcome.
| 
| I'll repeat my example and add what I meant with Within B it can only
| be referred to as C.F:
| 
| -- A.hs
| module A where
| 
| import B
| 
| -- B.hs
| {-# LANGUAGE TypeFamilies #-}
| 
| module B where
| 
| import qualified C
| 
| data B1 a = B1 a
| 
| instance C.C1 (B1 a) where
|   data C.F (B1 a) = B2 a
| 
| data family D a
| 
| -- C.hs
| {-# LANGUAGE TypeFamilies #-}
| module C where
| 
| class C1 a where
|   data F a :: *
| 
| -- ghci 7.2.1
| ghci A
| *A :info F
| data family F a   -- Defined at C.hs:6:8
| 
| ghci B
| *B :browse
| data B1 a = B1 a
| data instance B.R:FB1 (B1 a) = B2 a
| data family D a
| data family F a
| *B :info F
| Top level: Not in scope: data constructor `F'
| *B :info C.F
| data family C.F a -- Defined at C.hs:6:8
| 
| -- ghci 7.0.4
| ghci A
| *A :info F
| Top level: Not in scope: data constructor `F'
| 
| ___
| 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


Superclass defaults

2011-08-15 Thread Simon Peyton-Jones
(Adding GHC users, and changing title.)

| Conor McBride wrote:
|  http://hackage.haskell.org/trac/ghc/wiki/DefaultSuperclassInstances
|  I don't know if it's likely to be implemented in GHC anytime soon,..
|  So things are looking up. It should soon be technically feasible to
|  separate the issues of whether the Monoid operator should be () and
|  whether it should actually live in a Semigroup superclass...
| 
| Nice. But will it be happening soon, or not? And how soon is
| soon?

Not soon enough to be useful for this mappend question.

But, concerning proposed extensions to GHC about class aliases/superclass 
defaults etc, the truth is that the biggest reason for inertia here at GHC HQ 
is not so much the implementation effort (athough that is always an issue).  
Rather, it's uncertainty about 

 (a) Is there a reasonably large group of users who really want such a change?  
 Or is it just nice to have?

 (b) What is the right design? 

 (c) Does it pay its way? (ie do the programming benefits justify the cost in 
terms of
 both language complexity and ongoing maintenance burden of one more 
feature 
 to bear in mind when changing anything)

With help from Conor we have made some progress on this: we have a draft design:
http://hackage.haskell.org/trac/ghc/wiki/DefaultSuperclassInstances

If you care about the issue, maybe you can help resolve the above questions. In 
particular, to give 
concrete evidence for (b), working out some case studies would be a Good Thing. 
The examples given in other proposals using the extension proposed here would 
be one starting point.

If someone felt able to act as moderator for the discussion, willing to 
summarise conclusions, open questions, and so on, on the wiki page, that would 
be enormously helpful.  I am in too many inner loops.   But I *am* willing to 
contemplate such an extension -- it has the same flavour as default methods 
themselves, which are a very useful part of H98.

Simon

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


RE: Superclass defaults

2011-08-15 Thread Simon Peyton-Jones

|  If someone felt able to act as moderator for the discussion, willing
|  to summarise conclusions, open questions, and so on, on the wiki
|  page, that would be enormously helpful.
| 
| I'm up for that role, if that's appropriate.

I'll take you up on that, thank you!  I've added some SLPJ note notes to 
http://hackage.haskell.org/trac/ghc/wiki/DefaultSuperclassInstances which could 
perhaps do with clarifying.

Simon

PS: to avoid spam, maybe now we have advertised this thread, we should restrict 
it to ghc-users?  The *current* library question about mappend etc can stay on 
libraries.

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


RE: Build failure of syb-with-class with ghc-7.2.1

2011-08-09 Thread Simon Peyton-Jones
No, it's more #5375 and #5307.  Email coming

S

| -Original Message-
| From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-users-
| boun...@haskell.org] On Behalf Of Sergei Trofimovich
| Sent: 09 August 2011 14:15
| To: Bas van Dijk
| Cc: glasgow-haskell-users@haskell.org
| Subject: Re: Build failure of syb-with-class with ghc-7.2.1
| 
|  the HEAD of syb-with-class fails with the following error when build
|  with ghc-7.2.1 and template-haskell-2.6:
| 
|  http://code.google.com/p/syb-with-class/issues/detail?id=4
| 
|  Is this a bug in TH?
| 
| Very likely:
| http://hackage.haskell.org/trac/ghc/ticket/5362
| 
| --
| 
|   Sergei

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


RE: Build failure of syb-with-class with ghc-7.2.1

2011-08-09 Thread Simon Peyton-Jones
In TH code you now need to use mkName at variable uses instead of the names 
created directly with newName. Repa had a similar problem.

Eh? I don't understand that.  Can you give a small example?

Simon

From: glasgow-haskell-users-boun...@haskell.org 
[mailto:glasgow-haskell-users-boun...@haskell.org] On Behalf Of Ben Lippmeier
Sent: 09 August 2011 14:44
To: Bas van Dijk
Cc: glasgow-haskell-users@haskell.org Mailing List
Subject: Re: Build failure of syb-with-class with ghc-7.2.1


On 09/08/2011, at 23:15 , Sergei Trofimovich wrote:


the HEAD of syb-with-class fails with the following error when build
with ghc-7.2.1 and template-haskell-2.6:

http://code.google.com/p/syb-with-class/issues/detail?id=4

Is this a bug in TH?

Very likely:
   http://hackage.haskell.org/trac/ghc/ticket/5362

In TH code you now need to use mkName at variable uses instead of the names 
created directly with newName. Repa had a similar problem.

Ben.


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


RE: Build failure of syb-with-class with ghc-7.2.1

2011-08-09 Thread Simon Peyton-Jones
Sigh.  See http://hackage.haskell.org/trac/ghc/ticket/5398#comment:1

Simon

| -Original Message-
| From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-users-
| boun...@haskell.org] On Behalf Of Bas van Dijk
| Sent: 09 August 2011 13:47
| To: glasgow-haskell-users@haskell.org
| Subject: Build failure of syb-with-class with ghc-7.2.1
| 
| Hello,
| 
| the HEAD of syb-with-class fails with the following error when build
| with ghc-7.2.1 and template-haskell-2.6:
| 
| http://code.google.com/p/syb-with-class/issues/detail?id=4
| 
| Is this a bug in TH?
| 
| Regards,
| 
| Bas
| 
| ___
| 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: System.Process.system in Windows

2011-08-04 Thread Simon Peyton-Jones
| I had a bit of fun recently tracking down quoting issues with the
| system command in Windows. For the examples below, I'll consistently
| use Windows  as the beginning of some text sent to the Windows
| command prompt cmd.exe, and use GHC  as the beginning of some text
| sent to a ghci session running in cmd.exe with System.Cmd imported.

I remember struggling with this, and failing.  We'd be thrilled if someone on 
this list felt up to taking up the cudgels and sorting it out.

I've created a ticket for it though!
http://hackage.haskell.org/trac/ghc/ticket/5376

Simon

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


RE: GHCJS

2011-08-04 Thread Simon Peyton-Jones
|  data LiteralDesugaring m =
|LiteralDesugaring
|  { desugarInt :: MonadThings m = Integer - m CoreExpr
|  , desugarWord :: MonadThings m = Integer - m CoreExpr
...

I am not sure why you want to control the desugaring of literals.  Why 
literals?  And why is literals enough?

|  But I don't still understand what can I do with foreign
|  imports/exports. DsForeign module seems to be too complicated. As I
|  can see, I shouldn't make whole dsForeigns function replaceable, but I
|  can't understand what part of it should be replaceble.

I still think that the stub generation for foreign declarations should be 
easily separable.   The desugarer generates a certainly amount of unwrapping, 
but you'll want that for JavaScript too. The actual calling convention is 
embedded inside the Id: see the FCallId constructor of IdDetails in IdInfo.lhs, 
and the ForeignCall type in ForiegnCall.lhs.

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


RE: GHCJS

2011-08-04 Thread Simon Peyton-Jones
|  So then parseDynamicFlags should be split into two layers, the lower
|  layer returning unused flags, and the upper layer generating errors.
| 
| It's not that simple. In
| ghcjs -O -someflag something -Wall
| is something an argument to someflag, or a file to be compiled?

It think it would be quite acceptable for GHC's parseDynamicFlags to consume 
any arguments that don't start with -, and treat them as filenames.  The new 
behaviour is that it might return any unrecognised flags starting with -.   
So flags for the JavaScript thing would have to look like
-foogle
or  -blag=33

This is not as flexible as the flag-spec Ian suggests, but it's *simple* and 
that is a real virtue.

Simon


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


RE: GHCJS

2011-08-03 Thread Simon Peyton-Jones
Victor

GHC is supposed to be extensible, via its API, so your questions are good ones. 
 However, there are things that that the API doesn't support, or supports 
badly, so it is not cast in stone.  Please suggest improvements -- and better 
still implement them. GHC evolves largely in response to your suggestions and 
help.

In particular I don't think anyone has implemented a new back end via the API 
(rather than by building it into GHC itself) before.  So this is good.  It 
would be cool to have a compiler that behaved as if it had a JavaScript backend 
built in, but was actually built in a modular way on the API. Then people could 
use that as a model to build new back ends.


I imagine that your general plan is:
 - use the GHC API to parse Hasekll, typecheck it, optimise it
 - finishing with a [CoreBind] of optimised definitions
 - then use your own code generator to convert that [CoreBind] into JavaScript

| == Command line interface ==
| This works, but I'm not allowed to parse some custom flags used by
| GHCJS code and not by GHC API.
| ParseDynamicFlags throws UsageError if it encounters some unknown flags.

So perhaps that's the problem. parseDynamicFlags could perfectly well simply 
return any un-recognised flags. Indeed, I thought it did just that -- it 
certainly returns a list of un-consumed arguments.  If it doesn't perhaps 
that's a bug.

| == Foreign Function Interface ==
| 
| What I want is to provide FFI for Javascript, But GHC doesn't allow to
| extend FFI declaration syntax.
| I'd like to create some new FFI calling convention (javascript) like this:
| 
| foreign import javascript alert
|   jsalert :: Ptr JSString - IO ()

OK, so this is harder.  Presumably you want to use an *unmodified* Haskell 
parser to parse the Haskell programs. Adding *syntactic* extensions is 
therefore somewhat invasive:
- change the lexer
- change the parser
- change the HsSyn data structure
- change every function that traverses HsSyn

However in this particular case maybe things are not so bad.  I believe that 
perhaps *all* you want is to add a new calling convention. See ForeignImport in 
HsDecls, and CCallConv in ForeignCall.  Simply adding a new data constructor to 
CCallConv, and lexing the token for it, would not be too bad.  We could 
possibly add that part to the mainline compiler. The compiler would largely 
ignore such decls, and they'd just pop out at the other end for your back end 
to consume.

There might be complications -- see DsForeign in particular -- but I expect 
they'd be minor.

| For now I'm using (abusing) ccall calling convention and simple
| imports works pretty well, but I would like to support
| exports and static/dynamic wrappers. GHC generates C-code to support
| them, and GHCJS should generate Javascript-code,
| but I have no idea how to use GHC API to generate custom (Javascript)
| stubs. Is it possible at all?

Well, GHC generates the stub code in its code generator, doesn't it?  If you 
don't call the code generator, because you are using yours instead, then it'll 
be up to you to generate the stub code, no?

| == Packages support ==
| 
| It will be very handy if users can use Cabal to install and build
| packages with GHCJS.
| It should work if I replicate ghc and ghc-pkg command line interface,
| but remaining problem is that
| package index and package directories will be shared with GHC,

I don't know about this.  Dunan or Simon may be able to help.

Simon

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


RE: Quoting a quasi-quote

2011-07-27 Thread Simon Peyton-Jones
Dear Template Haskell users

There was a little exchange about TH quasiquotes a few weeks back (see below).  
I've made a ticket and some concrete proposals here
http://hackage.haskell.org/trac/ghc/ticket/5348

Do take a look, if you care about TH quasiquotes.

Simon

| -Original Message-
| From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-users-
| boun...@haskell.org] On Behalf Of Simon Marlow
| Sent: 11 July 2011 13:43
| To: g...@sefer.org
| Cc: GHC users; Ben Millwood
| Subject: Re: Quoting a quasi-quote
| 
| On 30/06/2011 14:52, Yitzchak Gale wrote:
|  It was pointed out by Ben Millwood on the Cafe
|  that there is an undocumented way to escape the
|  closing oxford bracket of a quasi-quote using
|  a backslash:
| 
|  [s|This quasi-quote contains this, \|], an escaped
|  closing oxford bracket.|]
| 
|  The backslash itself cannot be escaped in this
|  way:
| 
|  [s|Also contains an escaped bracket \\|] |]
| 
|  Thus there is a fairly strong limitation on the
|  contents of a quasi-quote: it can never end
|  in a backslash.
| 
|  This behavior is not mentioned in the GHC docs.
|  Is it a mistake, or is it meant to be a supported
|  feature?
| 
|  This behavior is a bit surprising to me. Since the
|  whole point of a quasi-quoter is to allow the user
|  to define syntax, you would think that the syntax
|  for the quasi-quote itself would be as quiet as
|  possible and stay out of the way. People who
|  need to be able to escape the closing bracket
|  can easily define their own syntax to do so.
| 
|  In any case, if this is indeed a feature, it certainly
|  should be documented.
| 
| It looks intentional to me:
| 
| lex_quasiquote :: String - P String
| lex_quasiquote s = do
|i - getInput
|case alexGetChar' i of
|  Nothing - lit_error i
| 
|  Just ('\\',i)
|   | Just ('|',i) - next - do
|   setInput i; lex_quasiquote ('|' : s)
|   | Just (']',i) - next - do
|   setInput i; lex_quasiquote (']' : s)
|   where next = alexGetChar' i
| 
|  Just ('|',i)
|   | Just (']',i) - next - do
|   setInput i; return s
|   where next = alexGetChar' i
| 
|  Just (c, i) - do
|setInput i; lex_quasiquote (c : s)
| 
| 
| Indeed, it also seems strange that \\] is interpreted as ].
| 
| That's all I know.  I agree we should either document or remove the feature.
| 
| Cheers,
|   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: Superclass Cycle via Associated Type

2011-07-25 Thread Simon Peyton-Jones
On further reflection I have a question.

Under the limited design below, which Edward says will do all he wants:

· The mutually recursive classes (call them A, B, C) must be defined 
all together. Like
   class B a = A a;  class C a = B a;  class A a = C a

· If a type T is an instance of any of those classes, it must be a 
member of all of them

· If a function f has type f :: A a = blah, then the signature f :: B 
a = blah and f :: C a = blah would work equally well

In short, I see no advantage to making A,B,C separate classes compared to 
simply unioning them into a single class.

Bottom line: adding recursive superclasses with the restrictions I describe 
below would add no useful expressive power.  But it would cost effort to 
implement. So why do it?

Maybe I’m missing something.

Simon

From: Edward Kmett [mailto:ekm...@gmail.com]
Sent: 22 July 2011 20:07
To: Simon Peyton-Jones
Cc: Gábor Lehel; glasgow-haskell-users@haskell.org
Subject: Re: Superclass Cycle via Associated Type

2011/7/22 Simon Peyton-Jones 
simo...@microsoft.commailto:simo...@microsoft.com
I talked to Dimitrios.  Fundamentally we think we should be able to handle 
recursive superclasses, albeit we have a bit more work to do on the type 
inference engine first.

The situation we think we can handle ok is stuff like Edward wants (I've 
removed all the methods):

class LeftModule Whole m = Additive m
class Additive m = Abelian m
class (Semiring r, Additive m) = LeftModule r m
class Multiplicative m where (*) :: m - m - m
class LeftModule Natural m = Monoidal m
class (Abelian m, Multiplicative m, LeftModule m m) = Semiring m
class (LeftModule Integer m, Monoidal m) = Group m
class Multiplicative m = Unital m
class (Monoidal r, Unital r, Semiring r) = Rig r
class (Rig r, Group r) = Ring r
The superclasses are recursive but
 a) They constrain only type variables
 b) The variables in the superclass context are all
mentioned in the head.  In class Q = C a b c
fv(Q) is subset of {a,b,c}

Question to all: is that enough?

This would perfectly address all of the needs that I have had!

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


RE: Superclass Cycle via Associated Type

2011-07-22 Thread Simon Peyton-Jones
I talked to Dimitrios.  Fundamentally we think we should be able to handle 
recursive superclasses, albeit we have a bit more work to do on the type 
inference engine first.  

The situation we think we can handle ok is stuff like Edward wants (I've 
removed all the methods):

class LeftModule Whole m = Additive m 
class Additive m = Abelian m
class (Semiring r, Additive m) = LeftModule r m 
class Multiplicative m where (*) :: m - m - m
class LeftModule Natural m = Monoidal m 
class (Abelian m, Multiplicative m, LeftModule m m) = Semiring m
class (LeftModule Integer m, Monoidal m) = Group m 
class Multiplicative m = Unital m 
class (Monoidal r, Unital r, Semiring r) = Rig 
class (Rig r, Group r) = Ring r

The superclasses are recursive but 
  a) They constrain only type variables
  b) The variables in the superclass context are all
 mentioned in the head.  In class Q = C a b c
 fv(Q) is subset of {a,b,c}

Question to all: is that enough?

=== The main difficulty with going further ==

Here's an extreme case
   class A [a] = A a where
  op :: a - Int

   f :: A a = a - Int
   f x = [x] + 1

The RHS of f needs A [a]
The type sig provides (A a), and hence (A [a]), 
and hence (A [[a]]) and so on.

BUT it's hard for the solver to spot all the now-infinite number of things that 
are provided by the type signature.

Gabor's example is less drastic
   class Immutable (Frozen a) = Mutable a where
  type Frozen a
   class Mutable (Thawed a) = Immutable a where
  type Thawed a

but not much less drastic.  (Mutable a) in a signature has a potentially 
infinite number of superclasses
Immutable (Frozen a)
Mutable (Thawed (Frozen a))
...etc...

It's not obvious how to deal with this.

However Gabor's example can perhaps be rendered with a MPTC:

 class (Frozen t ~ f, Thawed f ~ t) = Mutable f t where
   type Frozen a
   type Thawed a
   unsafeFreeze :: t - Frozen t
   unsafeThaw :: f - Thawed f

And you can do *that* today.

Simon

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


RE: Superclass Cycle via Associated Type

2011-07-21 Thread Simon Peyton-Jones
You point is that the (C Int) dictionary has (C String) as a superclass, and (C 
String) has (C Int) as a superclass. So the two instances are mutually 
recursive, but that's ok.

That is not unreasonable. But it is dangerous. Consider
 class C [a] = C a
Then any dictionary for (C a) would contain a dictionary for (C [a]) which 
would contain a dictionary for C [[a]], and so on.  Haskell is lazy so we might 
even be able to build this infinite dictionary, but it *is* infinite.

It's a bit like the recursive instance stuff introduced in Scrap your 
boilerplate with class.

After 5 mins thought I can't see a reason why this could not be made to work.  
But it'd take work to do.  If you have a compelling application maybe you can 
open a feature request ticket, describing it, and referring this thread?

Has anyone else come across this?

Simon

From: glasgow-haskell-users-boun...@haskell.org 
[mailto:glasgow-haskell-users-boun...@haskell.org] On Behalf Of Ryan Trinkle
Sent: 20 July 2011 17:37
To: glasgow-haskell-users@haskell.org
Subject: Superclass Cycle via Associated Type

The following code doesn't compile, but it seems sensible enough to me.  Is 
this a limitation of GHC or is there something I'm missing?




class C (A x) = C x where

  type A x :: *



instance C Int where

  type A Int = String



instance C String where

  type A String = Int





The error I get is:





SuperclassCycle.hs:1:1:

Cycle in class declarations (via superclasses):

  SuperclassCycle.hs:(1,1)-(2,15): class C (A x) = C x where {

   type family A x :: *; }









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


Deriving Typeable -- possible improvement

2011-07-14 Thread Simon Peyton-Jones
| iterIO uses mkTyCon for the simple reason that ((Typeable t, Typeable
| m) = Iter t m) is Typeable1 and there is no automatic way of deriving
| Typeable1.

This email is triggered by a thread on Haskell Cafe about changes to the 
Typeable class
http://www.mail-archive.com/haskell-cafe@haskell.org/msg91830.html
It proposes a modification to the way Typeable is derived; and concludes with a 
question.

Simon


David Mazieres and others comment that you can't derive Typeable for types like 
this:
data T f = MkT (f Int)
So he defines his own instance like this
[C] instance Typable1 f = Typeable (T f) where
  typeOf = ...

So why can't GHC do this?  Well, here's what GHC does. Given a bog standard 
data type like Maybe
data Maybe a = Nothing | Just a deriving( Typeable )
GHC generates this instance
[A] instance Typeable1 Maybe where
   typeOf = ...
Remember that Typeable1 takes a type *constructor*, of kind (*-*), as its 
argument.

Now if we need (Typeable (Maybe Int)), GHC first uses an instance from the 
Typeable library:
[B] instance (Typeable1 f, Typeable a) = Typeable (f a) where
  typeOf = ...

And now it uses the (Typeable1 Maybe) instance [A].  So it's kind of cool... 
the applications are decomposed by [B], leaving the tycon to [A].


But this doesn't work for T above.  We can't make (Typeable1 T) because T has 
kind ((*-*)-*), not (*-*) as Typeable1 requires.  Hence David defining his 
own instance.

GHC could do this too.  Indeed it could do so for Maybe too, thus:
instance Typeable a = Typeable (Maybe a) where 
  typeOf = ...

But then, alas, we could not get (Typeable (T Maybe)), because [C] needs Maybe 
to be in Typeable1.

== PROPOSAL ==
So here is a compromise, which would at least do better than the current story:

When deriving Typeable for a data type S of kind
S :: k1 - .. - kn - * - ... - *
(where kn is not *, and there are M trailing * arguments),
generate the instance
   instance (Typeable_x1 a1, ..., Typeable_xn an)
= TypeableM (S a1 .. an)

That is, knock off all the trailing * args, and then generate an instance for 
the remaining stub. 

= EXAMPLE 
Example from iterIO:

newtype Iter (t :: *) (m :: *-*) (a :: *)
   = Iter { runIter :: Chunk t - IterR t m a }
   deriving( Typeable )

This should generate

instance (Typeable t, Typeable1 m) = Typeable1 (Iter t m) 

where we knock off the trailing (a :: *) argument.

== QUESTION =
This approach is not beautiful.  It does not solve the underlying problem, 
which is a lack of kind polymorphism, but that is a battle for another day.  
Until that day, this alternative way of deriving Typeable would automate 
significantly more cases, I think.  Of course, it also makes it more 
complicated to explain when deriving Typeable will succeed.

Any opinions?  Does anyone care?

Simon


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


RE: Type function under a forall type

2011-06-23 Thread Simon Peyton-Jones
Dimitrios and I don't think there is a fundamental difficulty here, but it 
involves some work on the constraint solver that we have not yet done, 
especially concerning the evidence that is constructed for a proof.

So it's on the list, but currently not very high priority. Yell if it's 
important to you.

There is a ticket about it: http://hackage.haskell.org/trac/ghc/ticket/4310, so 
add yourself to the cc list if you care about it.

Simon

| -Original Message-
| From: Stefan Holdermans [mailto:ste...@vectorfabrics.com]
| Sent: 21 June 2011 10:51
| To: Simon Peyton-Jones; Tom Schrijvers
| Cc: glasgow-haskell-users@haskell.org
| Subject: Type function under a forall type
| 
| Simon, Tom,
| 
| I hit this type-error message in GHC 7.0.3:
| 
|   Cannot deal with a type function under a forall type:
|   forall e. El e u
| 
| Is there a fundamental reason why type functions under a forall type are a 
bad idea?
| Of is it just something that hasn't been implemented/thought about yet?
| 
| Cheers,
| 
|   Stefan

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


RE: [GHC] #5051: Typechecker behaviour change

2011-06-23 Thread Simon Peyton-Jones
I believe that's right.

Simon

| -Original Message-
| From: glasgow-haskell-bugs-boun...@haskell.org [mailto:glasgow-haskell-bugs-
| boun...@haskell.org] On Behalf Of Serge D. Mechveliani
| Sent: 23 June 2011 11:03
| To: glasgow-haskell-b...@haskell.org
| Cc: glasgow-haskell-users@haskell.org
| Subject: Re: [GHC] #5051: Typechecker behaviour change
| 
| Simon,
| thank you.
| 
| Currently,  DoCon  works under  ghc-7.0.1.
| And as I understand, the next release which is going to support DoCon
| (with its heavy use of overlapping instances) will be  ghc-7.2.
| 
| Regards,
| 
| Serge Mechveliani,  mech...@botik.ru
| 
| 
| On Wed, Jun 22, 2011 at 11:01:53AM -, GHC wrote:
|  #5051: Typechecker behaviour change
|  ---+
|Reporter:  igloo |  Owner:  simonpj
|Type:  bug   | Status:  closed
|Priority:  high  |  Milestone:  7.2.1
|   Component:  Compiler  |Version:  7.0.2
|  Resolution:  fixed |   Keywords:
| 
|  [..]
| 
|   GHC 7 indeed falls over on `DoCon` 2.12.  It turns out to be a rather
|   subtle interaction of overlapping instances with the ill-fated silent
|   superclass parameters I introduced to solve a problem in the
|   typechecker's constraint solver.
|  [..]
| 
| ___
| Glasgow-haskell-bugs mailing list
| glasgow-haskell-b...@haskell.org
| http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


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


Superclass equalities

2011-06-22 Thread Simon Peyton-Jones
Friends

I have long advertised a plan to allow so-called superclass equalities.  I've 
just pushed patches to implement them. So now you can write

class (F a ~ b) = C a b where  { ... }

This email is just to encourage you to try them out.  

Currently this is just in the HEAD git repository.  It'll appear in GHC 7.2, a 
release we are now actively preparing.  But the feature isn't heavily tested 
(since it didn't exist until today), so I'd appreciate people trying it out.

Thanks

Simon

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


GHC and Haskell 98

2011-06-17 Thread Simon Peyton-Jones
Friends, this is to ask your opinion about a possible change in GHC 7.2.  The 
current implementation in GHC 7.2 is Plan A below.  Plan A is a bit easier for 
us, but I think it may be a bit draconian, and therefore propose Plan B as an 
alternative.  Opinions?

Simon

==
With GHC 7.0 if you say
ghc -c Main.hs
the import of Prelude, whether implicit or explicit, will come from package 
'base'.   This is also true if you say
ghc -c Main.hs -package haskell98
The package 'haskell98' exposes 'List' and 'Random' but not 'Prelude'.  That 
still comes from 'base'.

This isn't good, because it means that if in the future we change 'Prelude' in 
package 'base', a Haskell98 module might fail to compile. And later iterations 
of Haskell might well want to expand or change the Prelude.

There appear to be two alternatives:

  (Plan A) Add a module 'Prelude' to package 'haskell98'.  
   Now you can compile a pure H98 program thus:
   ghc -c Main.hs -hide-all-packages -package haskell98
   (Cabal puts the -hide-all-packages in for you.)  And this will 
   continue to work even if later iterations of Haskell change the 
Prelude.

BUT (A) means that this module becomes un-compilable:
module Main where
  import Random
  import Data.List
Why?  Because 'Random' comes from 'haskell98' and 'Data.List' comes from 
'base'. But if you say
ghc -c Main.hs -package base -package haskell98
then the (implicit) import of 'Prelude' will say Ambiguous module name: 
Prelude, because it's exported by both 'base' and 'haskell98'.  To fix this 
you have to change 'import Random' to 'import System.Random'. But the latter's 
API is different, so you may have to change the source code that uses it.

So the second alternative is this:

  (Plan B) Like Plan A, but in addition, if you say {-# LANGUAGE Haskell98 #-}
   in the file, or -XHaskell98 on the command line, the implicit import
   of Prelude comes from package 'haskell98', provided -package 
haskell98
   is specified, but regardless of what other in-scope packages expose 
   a Prelude module.

   Variation: an explicit 'import Prelude' is similarly directed to
   package 'haskell98' as well.


So:Under Plan A, some Hackage packages will become un-compilable,
   and will require source code changes to fix them.  I do not have
any idea how many Hackage packages would fail in this way.

   Unser Plan B, Hackage package that compile now will continue 
to compile, if their Cabal file is altered. No source code changes.
(Well, unless they depend on some innards of GHC.IO or
something like that.)

But Plan A is simpler. And by breaking packages it will encourage [force] 
libraries that use a mixture of H98 and more modern modules to move towards the 
more modern story.


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


RE: ghc cyclic import error confusing

2011-06-14 Thread Simon Peyton-Jones
Following Bryan's suggestion I've improved GHC's error message when there's a 
module cycle:

  Module imports form a cycle:
module `Foo4' imports `Foo'
which imports `Foo2'
which imports `Foo3'
which imports `Foo4'

Simon

| -Original Message-
| From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-users-
| boun...@haskell.org] On Behalf Of Bryan Richter
| Sent: 14 April 2011 18:24
| To: glasgow-haskell-users@haskell.org
| Subject: Re: ghc cyclic import error confusing
| 
| On Wed, Apr 13, 2011 at 11:44:33AM +0100, Simon Marlow wrote:
|  On 09/04/2011 04:32, Evan Laforge wrote:
|  I've found ghc's cyclic import error to be rather confusing, and I
|  finally took the time to understand why.  Here's an example:
|  
|  Module imports form a cycle for modules:
|Cmd.Cmd (./Cmd/Cmd.hs)
|  imports: Perform.Midi.Instrument Instrument.MidiDb Instrument.Db
|Perform.Midi.Instrument (./Perform/Midi/Instrument.hs)
|  imports: Cmd.Cmd
|Instrument.MidiDb (./Instrument/MidiDb.hs)
|  imports: Perform.Midi.Instrument
|Instrument.Db (./Instrument/Db.hs)
|  imports: Instrument.Search Instrument.MidiDb
|   Perform.Midi.Instrument
|Instrument.Search (./Instrument/Search.hs)
|  imports: Instrument.MidiDb Perform.Midi.Instrument
|  
|  It seems to be in a strange order and mentions extraneous modules.  I
|  would find this much easier to read:
|  
|  Perform.Midi.Instrument -  Cmd.Cmd -  Instrument.MidiDb -
|  Perform.Midi.Instrument
| 
|  So the algorithm that GHC uses is this:
| 
|- do a strongly connected component analysis
|- build until we hit a cycle
|- then, report the error for the cycle
| 
|  Now, the modules in the cycle are a strongly connected component:
|  every module is reachable from every other module by following
|  imports.  We report all the modules in the strongly connected
|  component and their imports, but omit imports of modules outside the
|  cycle.
| 
|  Instead, the order goes Cmd.Cmd -  Instrument.MidiDb, and then goes
|  backwards to Perform.Midi.Instrument -  Cmd.Cmd.  Then it goes
|  forward again to Instrument.MidiDb -  Perform.Midi.Instrument.  So
|  the order makes you jump around if you want to trace the import
|  chain.  The duplicated module that joins the cycle is not visually 
highlighted.
|  Whats more, it further confuses the eye by merging in multiple loops.
|  I suppose it could be useful to include additional loops, but I would
|  find it easier to read if they were included on their own line, such
|  as:
|  
|  Cmd.Cmd -  Instrument.Db -  Instrument.Search -
|  Perform.Midi.Instrument -  Cmd.Cmd
|  
|  However, I think probably the shortest loop is the most interesting
|  one, and if there are multiple shortest loops, simply picking one
|  randomly is likely to be sufficient.
| 
|  Picking the shortest one sounds reasonable.  However, there could be a
|  single edge which if removed will break all the loops, and they might
|  want to know which it is.
| 
|  If you want to play with this, the code is very localised: it is a few
|  lines in GhcMake.cyclicModuleError
| 
|  http://hackage.haskell.org/trac/ghc/browser/compiler/main/GhcMake.hs#L
|  1446
| 
| Hi Simon and Evan,
| 
| Thanks for bringing up a problem, and providing useful information about it, 
in a way
| that is understandable enough for a newcomer to have an opinion about it!
| 
| So, here is my newcomer's opinion: The error displays a strongly connected 
graph,
| with one or more cycles, but labels it a cycle. As you both point out, 
having all
| the information about the strongly connected modules is very useful. Labeling 
it a
| cycle, however, gives the reader an expectation that is bound to be 
confounded.
| 
| Perhaps the following change would be sufficient?
| 
| 
| 
| --- tmp/GhcMake.hs~   2011-04-14 09:46:02.177298318 -0700
| +++ tmp/GhcMake.hs2011-04-14 09:52:25.121290827 -0700
| @@ -1460,7 +1460,8 @@
| 
|  cyclicModuleErr :: [ModSummary] - SDoc  cyclicModuleErr ms
| -  = hang (ptext (sLit Module imports form a cycle for modules:))
| +  = hang (ptext (sLit Module imports form a strongly connected graph,
| + with one or more cycles, for these modules:))
| 2 (vcat (map show_one ms))
|where
|  mods_in_cycle = map ms_mod_name ms
| 
| 
| 
| 
| 
| -Bryan
| 
| P.S. I'm not sure what the accepted method for formatting/wrapping string 
literals
| is, so I left it as an exercise. :)


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


RE: MonoLocalBinds and hoopl

2011-06-14 Thread Simon Peyton-Jones
That is an interesting thought.  As it happens, each binding records what its 
free variables are, so it would not be hard to check whether all the free 
variables were top-level-bound.

Of course, it would make the rule a bit more complicated.  Rather than
only top level bindings are generalised
it would be
only binding groups whose free variables are top-level are generalised

Mind you, the rule is complicated already; for example bang-patterns are not 
generalised.  So maybe this would be no worse.

I must say I'm inclined to adopt this idea.  Any comments from others?

Simon

| -Original Message-
| From: Edward Z. Yang [mailto:ezy...@mit.edu]
| Sent: 14 June 2011 14:04
| To: glasgow-haskell-users; Simon Peyton-Jones
| Subject: Re: MonoLocalBinds and hoopl
| 
| I ran into some more code like this, and I realized there was something
| pretty important: the majority of let-bindings do not have any free varaibles.
| They could very well be floated to the top level without having to make any
| source level changes.
| 
| So maybe let should be generalized, if no free variables are captured.
| Some food for thought.
| 
| Cheers,
| Edward
| 
| Excerpts from Edward Z. Yang's message of Thu Dec 09 10:28:20 -0500 2010:
|  Hello all,
| 
|  Here's an experience report for porting hoopl to manage MonoLocalBinds.  The
|  Compiler.Hoop.XUtil module has a rather interesting (but probably common) 
style of
| code
|  writing, along the lines of this:
| 
|  fbnf3 (ff, fm, fl) block = unFF3 $ scottFoldBlock (ScottBlock f m l cat) 
block
|  where f n = FF3 $ ff n
|m n = FF3 $ fm n
|l n = FF3 $ fl n
|FF3 f `cat` FF3 f' = FF3 $ f' . f
| 
|  f, m, l and cat are polymorphic functions that are only used once in the
|  main expression, and are floated outside to improve readability.  However, 
when
|  MonoLocalBinds is turned on, these all become monomorphic and the 
definitions
|  fail.  In contrast, this (uglier) version typechecks:
| 
|  fbnf3 (ff, fm, fl) block = unFF3 $ scottFoldBlock (ScottBlock (FF3 . ff) 
(FF3 . fm)
| (FF3 . fl) (\(FF3 f) (FF3 f') - FF3 $ f' . f)) block
| 
|  One suggestion that I had was that we should generalize local bindings that
|  are only used once, but Marlow pointed out that this would make the 
typechecker
|  more complex and I probably would agree.
| 
|  As a userspace developer, I have two options:
| 
|  1. Bite the bullet and put in the polymorphic type signatures (which
| can be quite hefty)
|  2. Inline the definitions
|  3. Move the polymorphic functions into the global namespace
| 
|  (3) and (2) are not so nice because it breaks the nice symmetry between 
these
|  definitions, which always define f, m, l for the many, many definitions in
|  Hoopl of this style.
| 
|  Cheers,
|  Edward
| 

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


RE: The role of INLINE and INLINABLE on recursive functions

2011-06-09 Thread Simon Peyton-Jones
INLINE:
- no effect for a recursive function
- for a non-recursive function, always inline a call that 
(a) is applied to as many args as the LHS of the defn
(b) has some interesting context.  Ie (\y x- f x y) doesn't
inline f

INLINEABLE
a) For type-class overloaded functions (including recursive ones)
- makes them auto-specialise at call sites in other modules
- allows SPECIALISE pragmas for them in other modules

b) For non-recursive functions, makes GHC willing, but not super-eager,
  to inline at call sites.  Ie just use GHC's usual inlining rules.
  The difference from not having the pragma is that the *original* 
  RHS is inlined (if GHC decides to) rather than the optimised RHS.
 
Does that help?  The dual role of INLINEABLE is a bit confusing.  And the 
utility of (b) isn't clear to me.


Simon

| -Original Message-
| From: Johan Tibell [mailto:johan.tib...@gmail.com]
| Sent: 09 June 2011 12:06
| To: Simon Peyton-Jones
| Subject: The role of INLINE and INLINABLE on recursive functions
| 
| Hi,
| 
| This comment on Trac got me curious:
| 
| Ok, we looked at this, and it turns out that 6.12.3 desugars `forever`
| differently: in 6.12, a local recursive `let` was introduced, which meant
| that `forever` could be inlined (and hence specialised) at every call
| site, whereas in 7.0 the desugarer leaves the function as a top-level
| recursive function which cannot be inlined.
| 
| The solution is to add an `INLINABLE` pragma for `forever`, which will
| allow it to be specialised at a call site.
| 
| What's the meaning of INLINE or INLINABLE on a recursive function?
| Normally we don't inline recursive functions (when would we stop
| inlining?) so it's unclear to me what the meaning of the pragmas would
| be in this cases. I know that INLINABLE on a recursive function that
| takes a type class dictionary leads to call site specialization of
| that function (but not inlining).
| 
| People often use this transformation to get recursive functions inlined:
| 
| f = ... f ...
| 
| f_transformed = go
|   where go = ... go ...
| {-# INLINE f_transformed #-}
| 
| Could we get the same result by just adding an INLINE pragma to the original 
f?
| 
| Cheers,
| Johan


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


RE: crash caused by generic visitor (?)

2011-06-09 Thread Simon Peyton-Jones
Great, thanks. I've added that link to the user-documentation page for the GHC 
API, here
http://haskell.org/haskellwiki/GHC/As_a_library#Links

Please do elaborate that page, which is a bit thin at the moment.  It should be 
easier to find supporting info about the GHC API.

Simon

| -Original Message-
| From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-users-
| boun...@haskell.org] On Behalf Of Ranjit Jhala
| Sent: 14 May 2011 17:52
| To: ghc-users
| Subject: Re: crash caused by generic visitor (?)
| 
| Hi all,
| 
| my apologies. Looks like the issue (and a fix!) is described here
| 
|   http://mistuke.wordpress.com/category/vsx/
| 
| Thanks,
| 
| Ranjit.
| 
| On May 13, 2011, at 4:34 PM, Ranjit Jhala wrote:
| 
|  Hi all,
| 
|  I'm trying to extract the set of identifiers that are read in given
|  source file.  To this end, I wrote the following code (full source at end.)
| 
|  
|  main
|   = do fname   - (!! 0) `fmap` getArgs
|tcm - loadTypecheckedSource fname
|putStrLn $ showPpr tcm   -- this works fine
|putStrLn $ showPpr $ allIds tcm  -- this causes the crash
|return ()
| 
|  allIds ::  Data a = a - [Id]
|  allIds = listify (\x - case (x :: Id) of _ - True)
|  
| 
|  and where:
| 
|  loadTypecheckedSource ::  FilePath - IO TypecheckedSource
| 
|  unfortunately, when I compile and run it, I get the dreaded:
| 
|  Bug: Bug: panic! (the 'impossible' happened)
|  (GHC version 7.0.3 for i386-unknown-linux):
|  placeHolderNames
| 
|  Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug
| 
|  Turns out that the problem is when the file contains a type annotation.
|  That is,
| 
|  ./Bug Test00.hs
| 
|  crashes, when Test00.hs is:
| 
|  module Test where
| 
|  x :: Int
|  x = 0
| 
|  but does not crash when the file is:
| 
|  module Test where
| 
|  x = 0
| 
|  Can anyone tell me why listify chokes in the latter case? (And how one might
|  get around the problem?) I include the full source below (compiled with: 
ghc --make
| Bug, using ghc 7.0.3)
| 
|  Thanks!
| 
|  Ranjit.
| 
|  
---
| ---
|  import GHC
|  import Outputable
|  import DynFlags (defaultDynFlags)
|  import GHC.Paths (libdir)
| 
|  import System.Environment (getArgs)
|  import Control.Monad
|  import qualified Data.List as L
|  import Data.Data
|  import Data.Generics.Schemes (listify)
| 
|  main
|   = do fname   - (!! 0) `fmap` getArgs
|tcm - loadTypecheckedSource fname
|putStrLn $ showPpr tcm   -- this works fine
|putStrLn $ showPpr $ allIds tcm  -- this causes the crash
|return ()
| 
|  allIds ::  Data a = a - [Id]
|  allIds = listify (\x - case (x :: Id) of _ - True)
| 
|  loadTypecheckedSource ::  FilePath - IO TypecheckedSource
|  loadTypecheckedSource fname
|   = defaultErrorHandler defaultDynFlags $
|   runGhc (Just libdir) $ do
| df  - getSessionDynFlags
| setSessionDynFlags df
| tgt - guessTarget fname Nothing
| setTargets [tgt]
| load LoadAllTargets
| res - load LoadAllTargets
| if failed res
|   then pprPanic Load Failed!! (text AAARGH!)
|   else tm_typechecked_source `fmap` getTypecheckedModule fname
| 
|  findModSummary ::  GhcMonad m = FilePath - m ModSummary
|  findModSummary fname
|   = do msums - depanal [] False
|case L.find ((fname ==) . ms_hspp_file) msums of
|  Just msum - return msum
|  Nothing   - pprPanic ModuleName Lookup Failed!! (text AARGHC!)
| 
|  getTypecheckedModule :: GhcMonad m = FilePath - m TypecheckedModule
|  getTypecheckedModule = findModSummary = parseModule = typecheckModule
| 
| 
| 
| 
| 
| ___
| 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: Type of an HsExpr

2011-05-26 Thread Simon Peyton-Jones
|  tcRnExpr :: HscEnv
|  - InteractiveContext
|  - LHsExpr RdrName
|  - IO (Messages, Maybe Type)
| 
|  from TcRnDriver?
| 
| 
| This is pretty close to what I need. Unfortunately, I have
| LhsExpr Id not RdrName.

Just to be clear
  LHsExpr RdrNameis just after parsing
  LHsExpr Name   is just after the renamer
  LHsExpr Id is just after the type checker

So if you have an LHsExpr Id you have a fully typechecked expression.

In principle, then, it should be straightforward to write a function
lhsExprType :: LHsExpr Id - Type

The only problem is that HsSyn is big: there are many constructors.  
Nevertheless, it should be entirely straightforward. If someone wants to try, 
I'll gladly review.  I agree that it would be useful.  For example in an IDE 
you might want to select a sub-expression and see its type.

Ranjit: if it'd be useful to you, you might be familiar enough by 
now...?

A hack is to desugar the expression to Core and use exprType, but that's very 
indirect and (as you observe) involves a monad for fresh names etc.

Let me know

| So, I guess the PostTcType is just not well defined within a ParsedModule.
| Thats why I use TypecheckedSource.

Correct.  As its name suggests PostTcType is only filled in post-typechecker.

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


RE: Type of a HsExpr

2011-05-19 Thread Simon Peyton-Jones
Maybe you want

tcRnExpr :: HscEnv
 - InteractiveContext
 - LHsExpr RdrName
 - IO (Messages, Maybe Type)

from TcRnDriver?



| -Original Message-
| From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-users-
| boun...@haskell.org] On Behalf Of Sven Urbanski
| Sent: 18 May 2011 18:14
| To: ghc-users
| Subject: Type of a HsExpr
| 
| Hi all,
| 
| I'm having a problem similar to Ranjit in the mail parsing types.
| 
| However, I want to get the type of an HsExpr:
| 
| getType :: HsExpr - Type
| 
| or something similar.
| 
| This should basically do what :t does in ghci, but for any given
| HsExpr (also it should not work on Strings).
| 
| 
| Looking at the ghc sources, I found
| 
| exprType :: CoreExpr - Type
| 
| which is pretty close to what i need.
| 
| 
| Another way of solving this, would be a function lik this:
| 
| hsExpr2CoreExpr :: HsExpr - CoreExpr
| 
| Than I could combine them like:
| 
| exprType . hsExpr2CoreExpr
| 
| 
| Any hints are very much appreciated,
| 
| Sven
| 
| ___
| 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: Proposal to incorporate Haskell.org

2011-05-11 Thread Simon Peyton-Jones
Dear haskell.org committee

Great stuff.  Thanks for getting this together.

Things I wondered about are:
- who will run the haskell.org entity?
- how are they chosen?  do they have fixed terms? 
- how are they accountable to the Haskell Community
  (eg an a brief annual report would be good; 
 since money is involved, accounts perhaps)

None of these look like being problems to me, but I think we should have a page 
that sets out these matters -- a kind of constitution for haskell.org, if you 
like -- as part of the process.

Simon

| -Original Message-
| From: libraries-boun...@haskell.org [mailto:libraries-boun...@haskell.org] On 
Behalf
| Of Don Stewart
| Sent: 10 May 2011 23:45
| To: hask...@haskell.org; Haskell Libraries; GHC Users Mailing List; 
haskell-cafe;
| commit...@haskell.org
| Subject: Proposal to incorporate Haskell.org
| 
| Hello everyone.
| 
| The haskell.org committee[1], in the interest of the long-term stability
| of the open source Haskell community infrastructure, has decided to
| incorporate haskell.org as a legal entity. This email outlines our
| recommendation, and seeks input from the community on this decision.
| 
| The committee's proposal is that haskell.org incorporate as an entity
| under the Software Freedom Conservancy umbrella organization (the same group
| that Darcs joined recently):
| 
| http://sfconservancy.org/
| 
| If we proceed with this move, haskell.org will be a legal entity, and
| registered as a non-profit, allowing us to more directly accept
| (US tax-deductible) donations, and to invest in assets that benefit the
| Haskell open source community.
| 
| We welcome your feedback on the proposal attached below.
| 
| -- Don Stewart (on behalf of the Haskell.org committee)
| 
| 
| 
| 
| 
| = A proposal for the incorporation of Haskell.org =
| 
| In recent years, haskell.org has started to receive assets, e.g. money from
| Google Summer Of Code, donations for Hackathons, and a Sparc machine for use 
in
| GHC development. We have also started spending this money: in particular, on
| hosting haskell.org itself. There is also interest in running fundraising
| drives for specific things such as Hackathon sponsorship and hosting fees.
| 
| However, haskell.org doesn't currently exist as a legal entity, meaning that
| these assets have had to be held on our behalf by other entities, such as
| Galois and various universities. This leads to tricky situations, with no-one
| being sure who should decide how the haskell.org assets can be used.
| 
| To solve these problems, we propose that haskell.org applies to become a 
member
| project of the Software Freedom Conservancy (SFC)
| http://conservancy.softwarefreedom.org/. The SFC is a non-profit 
organization
| that provides free financial and administrative services to open source
| projects. Additionally, it has 501(c)(3) status, meaning donations from the US
| are tax-deductible. The SFC would hold haskell.org's money and other assets,
| and would be able to accept donations on behalf of haskell.org.
| 
| The haskell.org committee, as described here [2], will make decisions on
| spending assets and other decisions related to governing the non-profit.
| 
| 
| Before proceeding, we are inviting input from the community in the form
| of specific objections or queries regarding the plan.
| 
| We've tried to answer some of the most likely questions:
| 
| Q: Does this mean that my Haskell project must now be covered by a
|  copyleft licence such as GPL?
| A: No, but Haskell projects using haskell.org resource should use an
| Open Source licence
|  http://www.opensource.org/licenses/alphabetical.
| 
| Q: Will it still be possible to use community.h.o to host
|  non-open-source material, such as academic papers?
| A: An overall minority of such content, as is the current situation, is
| not a problem.
| 
| Q: Will it still be possible to have job ads on the haskell.org mailing
| lists and website?
| A: Yes.
| 
| Q: Will this affect our ability to host the Haskell Symposium
| http://www.haskell.org/haskell-symposium/  and Industrial Haskell
| Grouphttp://industry.haskell.org/  webpages within haskell.org?
| A: No.
| 
| Q: What will be the relationship between haskell.org and other
| organizations such as the Haskell Symposium and Industrial Haskell
| Group?
| A: Those organisations will continue to exist as separate entities.
| 
| Q: If an umbrella non-profit organisation The Haskell Foundation was
| created, would haskell.org be able to join it?
| A: Yes. It's likely that in such a scenario, the Haskell Foundation
| would become the owner of the haskell.org domain name, with the cost
| divided between the members. The entity that is part of the SFC would
| be renamed community.haskell.org in order to avoid confusion.
| 
| [1]: 

RE: performance issues in simple arithmetic code

2011-04-28 Thread Simon Peyton-Jones
|  cmm/CmmLex.x) to understand textual C--.  Note that there is also a new C--
|  representation hanging around that is not too interesting for you, since we 
don't
|  use it at all without the flag -fnew-codegen.

Although ultimately we hope to move to the new rep and abandon the old one.

Simon

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


RE: parsing types

2011-04-27 Thread Simon Peyton-Jones
Ah, well, yes, if you want to get an existing, *uncompiled* module into the 
ambient context, then of course you must compile it.  Glad you are unstuck.

Simon

| -Original Message-
| From: Ranjit Jhala [mailto:rjh...@eng.ucsd.edu] On Behalf Of Ranjit Jhala
| Sent: 27 April 2011 00:42
| To: Simon Peyton-Jones; Daniel Peebles; Thomas Schilling
| Cc: ghc-users
| Subject: Re: parsing types
| 
| Dear Simon, Daniel and Thomas,
| 
| thanks for your help with this! I managed to get what I
| want by writing something like so:
| 
| tcExpr ::  FilePath - String - IO Type
| tcExpr f s =
|   defaultErrorHandler defaultDynFlags $
| runGhc (Just libdir) $ do
|   df   - getSessionDynFlags
|   setSessionDynFlags df
|   cm   - compileToCoreModule f
|   setContext [(cm_module cm)] []
|   env  - getSession
|   r- hscTcExpr env s
|   return r
| 
| In short, I take the filepath, compile it to a module, then
| add that to the context and then extract the env and typecheck.
| If there's a shorter route, I'm all ears, but this seems to
| get the job done...
| 
| Thanks again!,
| 
| Ranjit.
| 
| 
| 
| 
| On Apr 26, 2011, at 3:13 AM, Simon Peyton-Jones wrote:
| 
|  Ranjit
| 
|  [NB: all of this is based on a quick look at the source code; I'm not that
| familiar with the GHC API, so others may correct me.]
| 
|  A good entry point to the GHC API is InteractiveEval.hs.  You'll see that
| all its functions are parameterised over a simple state monad (GhcMonad m),
| which is any monad supporting
|   getSession :: m HscEnv
|   setSession :: HscEnv - m ()
| 
|  The HscEnv encapsulates all the persistent state of the session, including
| the ambient modules; in a GHCi session these are the ones you have
| imported to the command line prompt.
| 
|  You can augment these ambient modules with InteractiveEval.setContext.
| (Its API is a bit confusing and it's on my list of things to change.)  So
| just call that to augment the context.
| 
|  Then you can call hscTcExpr. [Maybe there should be a GhcMonad version of
| this function, with the type sig you give.  The one in HscMain isn't.]
| 
|  Does that help?
| 
|  Simon
| 
|  | -Original Message-
|  | From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-
|  | users-boun...@haskell.org] On Behalf Of Ranjit Jhala
|  | Sent: 24 April 2011 02:27
|  | To: Daniel Peebles
|  | Cc: ghc-users
|  | Subject: Re: parsing types
|  |
|  | Hi Daniel --
|  |
|  | that was a good lead, with a little digging around, I found
|  |
|  |   hscTcExpr :: GhcMonad m = HscEnv - String - m Type
|  |
|  | which almost gets the job done, if only I could call it with
|  | the appropriate HscEnv. The one I get using
|  |
|  |   getSession :: GhcMonad m = m HscEnv
|  |
|  | appears rather impoverished, as it fails to find the usual
|  | prelude names like
|  |
|  |   Not in scope: `undefined'
|  |   Not in scope: `error'
|  |
|  | (though it does succeed on the expression 5 yielding the type)
|  |
|  | forall t_a4eW. (GHC.Num.Num t_a4eW) = t_a4eW
|  |
|  | Does anyone have a clue as to how to get a hold on an appropriate
|  | environment? (I would have thought that the HscEnv obtained _after_
|  | compiling some file f would populated with at least the names
|  | needed to compile f) that is, if I do:
|  |
|  |   cm0  - compileToCoreSimplified f
|  |   env  - getSession
|  |
|  | then the resulting env would suffice, but unfortunately thats not
|  | the case...
|  |
|  | Thanks!,
|  |
|  | Ranjit.
|  |
|  |
|  |
|  |
|  |
|  |
|  |
|  |
|  | On Apr 23, 2011, at 11:54 AM, Daniel Peebles wrote:
|  |
|  |  I don't have an answer for you, but you might want to look at what :k
| does
|  | in ghci, since that needs to parse a type.
|  | 
|  |  On Sat, Apr 23, 2011 at 2:06 PM, Ranjit Jhala jh...@cs.ucsd.edu
| wrote:
|  |  Hi all,
|  | 
|  |  can someone give me a hint as to the best way to parse a type from a
|  | string.
|  |  Ideally, I'd like a function
|  | 
|  | stringType :: String - Maybe Type
|  | 
|  |  or possibly,
|  | 
|  | stringType :: (GhcMonad m) = String - m (Maybe Type)
|  | 
|  |  such that,
|  | 
|  | stringType s == Just t
|  | 
|  |  if in the current GHC context the string s is the name of the type t.
| For
|  |  example, I'd like:
|  | 
|  | stringType Int
|  | 
|  |  to return a value equal to intTy (from TysWiredIn). My investigations
| have
|  |  led me to
|  | 
|  | parseType :: P (LHsType RdrName)
|  | 
|  |  and I suspect that with some work (mainly creating an appropriate
| PState,
|  |  and mapping the name back, I can extract what I want, but I was
| wondering
|  |  if there is some simpler route that I've overlooked.
|  | 
|  |  Thanks!
|  | 
|  |  Ranjit.
|  | 
|  |  ___
|  |  Glasgow-haskell-users mailing list
|  |  Glasgow-haskell-users@haskell.org
|  |  http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

RE: Perplexing GHC-7.0.3 behavior with hairy type-level code (regression from 6.12.3??)

2011-04-26 Thread Simon Peyton-Jones
It's hard to say much without a particular program to look at.  But when type 
families or functional dependencies are involved you can certainly get 
situations where
f :: ty
but if you write

g ::ty
g = f

the program is rejected.  Sounds similar to what you are seeing.  Look here:

http://www.haskell.org/haskellwiki/GHC/Type_families#Injectivity.2C_type_inference.2C_and_ambiguity

If you are still puzzled, by all means try to boil out a test case, the smaller 
the better.   A bug is far from impossible.

Simon

|  -Original Message-
|  From: glasgow-haskell-users-boun...@haskell.org 
[mailto:glasgow-haskell-users-
|  boun...@haskell.org] On Behalf Of Bjorn Buckwalter
|  Sent: 22 April 2011 16:19
|  To: GHC Users
|  Subject: Perplexing GHC-7.0.3 behavior with hairy type-level code 
(regression from
|  6.12.3??)
|  
|  Hello all,
|  
|  I am doing some fairly hairy type-level stuff with
|  FunctionalDependencies, UndecidableInstances, and other. Without going
|  into details I have the following function which compiles fine:
|  
|vecMat :: (Transpose m m', MatrixVector m' v v', Num a)
|   = Vec v a - Mat m a - Vec v' a
|vecMat v m = transpose m `matVec` v
|  
|  
|  However, I am perplexed by the following:
|  
|  1. This does NOT compile despite the type signature being identical to
|  that of 'vecMat':
|  
|vecMat2 :: (Transpose m m', MatrixVector m' v v', Num a)
|= Vec v a - Mat m a - Vec v' a
|vecMat2 v m = vecMat v m
|  
|  The error message is along the lines of the below where 'HMap ...' is
|  the context for the MatrixVector instance... I'll provide more details
|  as needed.
|  
|  Could not deduce (HMap (DotProd, v) m' v')
|arising from a use of `vecMat'
|  from the context (Transpose m m', MatrixVector m' v v', Num a)
|bound by the type signature for
|   vecMat2 :: (Transpose m m', MatrixVector m' v v', Num a) =
|  Vec v a - Mat m a - Vec v' a
|  
|  
|  2. If I omit the type signature the definition of 'vecMat2' does compile:
|  
|vecMat2 v m = vecMat v m
|  
|  3. If I omit the second argument it also compiles:
|  
|vecMat2 v = vecMat v
|  
|  4. However, if I omit both arguments it does NOT compile:
|  
|vecMat2 = vecMat
|  
|  
|  So I guess I have two questions. First: why would 1 not compile?
|  Second: why are 2, 3, and 4 not equivalent? Pointers to relevant
|  documentation welcome.
|  
|  I broke my GHC-6.12.3 installation when upgrading to the latest HP
|  with GHC-7.0.3 so I cannot test 2, 3, and 4 but I know that 1 DID
|  compile on GHC-6.12.3. Is the change of behavior in GHC-7.0.3 a bug or
|  a bug fix?
|  
|  I'll be happy to elaborate on the code if it would be useful, and try
|  to find a minimal example. But I wanted to check if the behavior I am
|  seeing makes any sense at all first. In case you cannot wait the
|  'matVec' definition is from:
|  
|  https://github.com/bjornbm/dimensional-
|  vectors/blob/master/Numeric/Units/Dimensional/LinearAlgebra/Matrix.hs
|  
|  
|  Thanks,
|  Bjorn
|  
|  ___
|  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: parsing types

2011-04-26 Thread Simon Peyton-Jones
Ranjit

[NB: all of this is based on a quick look at the source code; I'm not that 
familiar with the GHC API, so others may correct me.]

A good entry point to the GHC API is InteractiveEval.hs.  You'll see that all 
its functions are parameterised over a simple state monad (GhcMonad m), which 
is any monad supporting 
  getSession :: m HscEnv
  setSession :: HscEnv - m ()

The HscEnv encapsulates all the persistent state of the session, including the 
ambient modules; in a GHCi session these are the ones you have imported to 
the command line prompt.

You can augment these ambient modules with InteractiveEval.setContext.  (Its 
API is a bit confusing and it's on my list of things to change.)  So just call 
that to augment the context.

Then you can call hscTcExpr. [Maybe there should be a GhcMonad version of this 
function, with the type sig you give.  The one in HscMain isn't.]

Does that help?

Simon

| -Original Message-
| From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-
| users-boun...@haskell.org] On Behalf Of Ranjit Jhala
| Sent: 24 April 2011 02:27
| To: Daniel Peebles
| Cc: ghc-users
| Subject: Re: parsing types
| 
| Hi Daniel --
| 
| that was a good lead, with a little digging around, I found
| 
|   hscTcExpr :: GhcMonad m = HscEnv - String - m Type
| 
| which almost gets the job done, if only I could call it with
| the appropriate HscEnv. The one I get using
| 
|   getSession :: GhcMonad m = m HscEnv
| 
| appears rather impoverished, as it fails to find the usual
| prelude names like
| 
|   Not in scope: `undefined'
|   Not in scope: `error'
| 
| (though it does succeed on the expression 5 yielding the type)
| 
| forall t_a4eW. (GHC.Num.Num t_a4eW) = t_a4eW
| 
| Does anyone have a clue as to how to get a hold on an appropriate
| environment? (I would have thought that the HscEnv obtained _after_
| compiling some file f would populated with at least the names
| needed to compile f) that is, if I do:
| 
|   cm0  - compileToCoreSimplified f
|   env  - getSession
| 
| then the resulting env would suffice, but unfortunately thats not
| the case...
| 
| Thanks!,
| 
| Ranjit.
| 
| 
| 
| 
| 
| 
| 
| 
| On Apr 23, 2011, at 11:54 AM, Daniel Peebles wrote:
| 
|  I don't have an answer for you, but you might want to look at what :k does
| in ghci, since that needs to parse a type.
| 
|  On Sat, Apr 23, 2011 at 2:06 PM, Ranjit Jhala jh...@cs.ucsd.edu wrote:
|  Hi all,
| 
|  can someone give me a hint as to the best way to parse a type from a
| string.
|  Ideally, I'd like a function
| 
| stringType :: String - Maybe Type
| 
|  or possibly,
| 
| stringType :: (GhcMonad m) = String - m (Maybe Type)
| 
|  such that,
| 
| stringType s == Just t
| 
|  if in the current GHC context the string s is the name of the type t. For
|  example, I'd like:
| 
| stringType Int
| 
|  to return a value equal to intTy (from TysWiredIn). My investigations have
|  led me to
| 
| parseType :: P (LHsType RdrName)
| 
|  and I suspect that with some work (mainly creating an appropriate PState,
|  and mapping the name back, I can extract what I want, but I was wondering
|  if there is some simpler route that I've overlooked.
| 
|  Thanks!
| 
|  Ranjit.
| 
|  ___
|  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


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


RE: [Haskell] Polymorphic types in RHS of type instances

2011-04-04 Thread Simon Peyton-Jones
Can you give an example of what you'd like to write, but can't?

Simon

From: glasgow-haskell-users-boun...@haskell.org 
[mailto:glasgow-haskell-users-boun...@haskell.org] On Behalf Of José Pedro 
Magalhães
Sent: 04 April 2011 10:53
To: GHC users
Cc: Steven Keuchel
Subject: Re: [Haskell] Polymorphic types in RHS of type instances

Hi,

[Moving to 
glasgow-haskell-users@haskell.orgmailto:glasgow-haskell-users@haskell.org]

I would also like to know the answer to this question. While I can imagine it 
has something to do with type checking/inference, it is not immediately clear 
to me where the problem lies.


Thanks,
Pedro
On Sat, Feb 5, 2011 at 12:25, Steven Keuchel 
steven.keuc...@gmail.commailto:steven.keuc...@gmail.com wrote:
Hi list,

I was wondering why GHC doesn't allow usage of polymorphic types in
the right-hand side of type instance declarations for type families.
The GHC user guide states: The right-hand side of a type instance
must be a monotype (i.e., it may not include foralls) [...], but it
doesn't state the reason.

I stumbled upon this limitation when I was trying to generically
calculate Johann's and Ghani's interpreter (transformers) for nested
data types from their Initial Algebra Semantics is Enough! paper.

Cheers,
Steven

___
Haskell mailing list
hask...@haskell.orgmailto:hask...@haskell.org
http://www.haskell.org/mailman/listinfo/haskell

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


RE: Issue with SrcSpan of AbsBinds

2011-03-25 Thread Simon Peyton-Jones
I don't think anyone has really looked at those SrcSpans before.  I'm fixing...

Simon

| -Original Message-
| From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-
| users-boun...@haskell.org] On Behalf Of JP Moresmau
| Sent: 18 March 2011 13:52
| To: glasgow-haskell-users@haskell.org
| Subject: Issue with SrcSpan of AbsBinds
| 
| Hello, I'm trying to get Scion to work well with GHC7, and I found a
| small issue (I'm not saying it's GHC7 only, maybe it was there in GHC
| 6.12). I'm using 7.0.2
| I have the following code, which is idiotic but proves the point:
| 
| fun ::  t - [Char] - [Char]
| fun _=reverse . map toUpper
| 
| And the TypecheckedSource gives me something like (using the
| ghc-syb-utils package to dump it:)
| 
| {Bag(Located (HsBind Var)):
|   [
|(L {src\Folder1\ForAll.hs:8:1-29}
| (AbsBinds
|  [{Var: t}]
|  []
|  [
|   ((,,,)
|[{Var: t}] {Var: Folder1.ForAll.fun} {Var: fun}
|(SpecPrags
| []))]
|  ({abstract:TcEvBinds}) {Bag(Located (HsBind Var)):
|  [
|   (L {src\Folder1\ForAll.hs:9:1-27}
|(FunBind
| (L {src\Folder1\ForAll.hs:9:1-3} {Var: fun})
| (False)
| (MatchGroup
| 
| Obviously my code starts at line 8 in that example.
| The issue occurs when the scion code wants to tell the user what
| (name+type) is a particular line/column in the source
| Now the scion code does something simple: to find something at a given
| point, it goes down the tree, and when it encounters a Located object,
| it checks the location spans around the point we're looking at. The
| issue here is that the AbsBinds has a SrcSpan that only covers the
| type signature, and not the rest of the code, hence (I think) we never
| go down the contents, and Scion cannot resolve anything when a user
| asks it to.
| If the type signature is not present, the problem doesn't occur: the
| AbsBinds location covers all the source code.
| If the type signature is present but without any type variable, there
| is no AbsBinds and no problem.
| 
| Is that normal behavior, and hence should I code a work around in Scion?
| 
| Thanks!
| 
| --
| JP Moresmau
| http://jpmoresmau.blogspot.com/
| 
| ___
| 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: Class constraints for associated type synonyms

2011-03-24 Thread Simon Peyton-Jones
| class Monoid (GeneratorOf a) = Generable a where
|   type GeneratorOf a :: * - *
|   construct :: GeneratorOf a - a
| 
| Now, it seems I need FlexibleInstances to do this when I'm using an
| associated type synonym, but I don't need the flexibility when using a
| multiparameter type class. 


Suppose you have these wierd instances:
type instance GeneratorOf (Tree a) = Tree (Tree a)
instance Generable a = Monoid (Tree a)
instance Generable (Tree a) 

Now, in the last of these we need to cough up an instance of Generable (Tree 
a)'s superclasses.  Ah, that's Monoid (GeneratorOf (Tree a))
Ah, that's Monoid (Tree (Tree a))
We have an instance of Monoid, but it needs, well Generable (Tree a), which is 
where we started. 

If I'd nested things a bit more deeply you can see I'd get into an infinite 
regress.   So you have to take responsibility that instance solving will 
terminate, hence FlexibleInstances.

As you say, the same thing can happen with fundeps. The fact that the thing is 
allowed is probably a bug in the Fundep stuff. 

Simon

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


RE: weird behaviour of context resolution with FlexibleContexts and TypeFamilies

2011-02-25 Thread Simon Peyton-Jones
You are doing something very delicate here, akin to overlapping instances.

You have an instance
instance PatchInspect (PrimOf p)) = Conflict p
and a function
clever :: (Conflict (OnPrim p), ..) = ...

So if a constraint (Conflict blah) arises in the RHS of clever, the instance 
declaration will immediately apply; and then the type check fails.  But if it 
just so happens to precisely match the provided constraint (Conflict (OnPrim 
p)), you want to use the provided constraint.  In effect the type signature and 
the instance overlap.

Arguably, GHC should refrain from applying the instance if there is any 
possibility of a given constraint matching.  Currently it's a bit random; but 
it's a very weird situation.

But first, is this really what you intend?

Simon

From: glasgow-haskell-users-boun...@haskell.org 
[mailto:glasgow-haskell-users-boun...@haskell.org] On Behalf Of Sittampalam, 
Ganesh
Sent: 24 February 2011 07:41
To: glasgow-haskell-users@haskell.org
Subject: weird behaviour of context resolution with FlexibleContexts and 
TypeFamilies


Hi,

If I build the code below with -DVER=2, I get a complaint about PatchInspect 
(PrimOf p) being missing from the context of cleverNamedResolve.

This doesn't happen with -DVER=1 or -DVER=3

I presume that type class resolution is operating slightly differently in the 
different cases, but it's quite confusing - in the original code joinPatches 
did something useful and I was trying to inline the known instance definition. 
I would have expected it to be consistent between all three cases, either 
requiring the context or not.

Is it a bug, or just one of the risks one takes by using FlexibleContexts?

I've tried this with GHC 6.12.3 and with 7.0.2RC2.

Cheers,

Ganesh

{-# LANGUAGE CPP, TypeFamilies, FlexibleContexts #-}
module Class ( cleverNamedResolve ) where

data FL p = FL p

class PatchInspect p where
instance PatchInspect p = PatchInspect (FL p) where

type family PrimOf p
type instance PrimOf (FL p) = PrimOf p

data WithName prim = WithName prim

instance PatchInspect prim = PatchInspect (WithName prim) where

class (PatchInspect (PrimOf p)) = Conflict p where
resolveConflicts :: p - PrimOf p

instance Conflict p = Conflict (FL p) where
resolveConflicts = undefined

type family OnPrim p

#if VER==1
class FromPrims p where

instance FromPrims (FL p) where

joinPatches :: FromPrims p = p - p
#else
#if VER==2
joinPatches :: FL p - FL p
#else
joinPatches :: p - p
#endif
#endif

joinPatches = id

cleverNamedResolve :: (Conflict (OnPrim p)
  ,PrimOf (OnPrim p) ~ WithName (PrimOf p))
   = FL (OnPrim p) - WithName (PrimOf p)
cleverNamedResolve = resolveConflicts . joinPatches



==
Please access the attached hyperlink for an important electronic communications 
disclaimer:
http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html
==

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


RE: Question about Haskell AST

2011-02-22 Thread Simon Peyton-Jones
I think the missing piece was Opt_Cpp.  Data.List uses the C preprocessor

S

| -Original Message-
| From: cvs-ghc-boun...@haskell.org [mailto:cvs-ghc-boun...@haskell.org] On
| Behalf Of Ian Lynagh
| Sent: 22 February 2011 15:09
| To: Jane Ren
| Cc: cvs-...@haskell.org; glasgow-haskell-users@haskell.org
| Subject: Re: Question about Haskell AST
| 
| 
| Hi Jane,
| 
| On Mon, Feb 21, 2011 at 11:46:16PM -0800, Jane Ren wrote:
| 
|  Did you mean I have to include the dflags like below to get the parsetree
| of a base library file like libraries/base/GHC/List.lhs
| 
|  I am stilling getting the same error
|  AstWalker: panic! (the 'impossible' happened)
|(GHC version 7.0.1 for x86_64-apple-darwin):
|  lexical error at character 'i'
| 
|  my code is  ...
|  setSessionDynFlags ...
|  target - guessTarget targetFile Nothing
|  setTargets [target]
|  load LoadAllTargets
| 
|  Would you have any other suggestions?
| 
| This works for me with the 7.0 branch:
| 
| main :: IO ()
| main =
| defaultErrorHandler defaultDynFlags $ do
|   runGhc (Just libdir) $ do
| dflags - getSessionDynFlags
| let dflags' = foldl xopt_set dflags
| [Opt_Cpp, Opt_ImplicitPrelude, Opt_MagicHash]
| setSessionDynFlags dflags'
| target - guessTarget fp Nothing
| setTargets [target]
| load LoadAllTargets
| liftIO $ putStrLn Done
| 
| Let me know if you still have problems.
| 
| 
| Thanks
| Ian
| 
| 
| ___
| Cvs-ghc mailing list
| cvs-...@haskell.org
| http://www.haskell.org/mailman/listinfo/cvs-ghc


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


RE: Injective type families?

2011-02-15 Thread Simon Peyton-Jones
shouldn't the check go the other way?  (i.e., if the RHSs unify, then the LHS 
must be the same).  Here is an example:

-- This function is not injective.
type instance F a = Int
type instance F b = Int

Yes, you’re right.

Still, Conal's example would not work if we just added support for injective 
type functions because + is not injective (e.g., 2 + 3 = 1 + 4).  Instead, what 
we'd need to say is that it is injective in each argument separately, which 
would basically amount to adding functional dependencies to type functions.  
Perhaps something like this:

type family (a :+: b) ~ c | c b - a, c a - b

Interesting!  Injectivity is more complicated than one might think!

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


RE: Trying to build Agda 2.2.9 with ghc-7.1.20110131

2011-02-14 Thread Simon Peyton-Jones
Pavel

Concerning Another one, the problem is that with BangPatterns enabled, GHC 
understands
  vs ! i = ...
to mean
  vs (!i) = ...
with a bang-pattern, thus defining vs rather than (!).  Reason: the common case 
 of saying
  f !x !y = e
is so convenient that we didn't want to require parens.  But the cost is that 
you can't define (!) in an infix way.  So that's that one.

For the profiling thing, is this the same as 
http://hackage.haskell.org/trac/ghc/ticket/4462?  What happens if you say 
-dcore-lint?We should look at #4462.

Simon

From: glasgow-haskell-users-boun...@haskell.org 
[mailto:glasgow-haskell-users-boun...@haskell.org] On Behalf Of Pavel Perikov
Sent: 01 February 2011 15:01
To: GHC users
Subject: Trying to build Agda 2.2.9 with ghc-7.1.20110131

If anyone interested...

Agda-2.2.9 compiled perfectly with 7.0.1 release but with 7.1.20110131 the 
compiler had a few problems including impossible happened when building 
profiling library.

Another one was in src/full/Agda/TypeChecking/Positivity.hs @ 260:
instance ComputeOccurrences Term where
  occurrences vars v = case v of
Var i args -
  maybe Map.empty here (vars ! fromIntegral i)
  ..
where
 vs ! i
 | i  length vs = vs !! i
 | otherwise = error $ show vs ++  !  ++ show i ++   ( ++ show 
v ++ )

Compiler complained about ! in vars ! fromIntegral suggesting Map.!

after i changed the code to

where
 (!) vs  i
 | i  length vs = vs !! i
 | otherwise = error $ show vs ++  !  ++ show i ++   ( ++ show 
v ++ )

everything proceeded as expected.

I also had to give -XFlexibleInstances and -XBangPatterns that was not required 
previously.
Agda can be got from
darcs get http://code.haskell.org/Agda/

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


RE: Injective type families?

2011-02-14 Thread Simon Peyton-Jones
Injective type families are a perfectly reasonable idea, but we have not 
implemented them (yet). The idea would be:

* You declare the family to be injective

injective type family T a :: *

* At every type instance, injectivity is checked.  That is, if you say

type instance T (a,Int) = Either a Bool

then we must check that every type instance whose LHS unifies with this has the 
same RHS under the unifying substitution.  Thus

type instance T (a,Bool) = [a]   -- OK; does not unify
type instance T (Int,b) = Either Int Bool  -- OK; same RHS on (Int,Int)


I think it's mainly a question of tiresome design questions (notably do we want 
a new keyword injective?  Should it go before type?) and hacking to get it 
all implemented.

Simon

|  -Original Message-
|  From: glasgow-haskell-users-boun...@haskell.org 
[mailto:glasgow-haskell-users-
|  boun...@haskell.org] On Behalf Of Dan Doel
|  Sent: 14 February 2011 23:14
|  To: glasgow-haskell-users@haskell.org
|  Subject: Re: Injective type families?
|  
|  On Monday 14 February 2011 5:51:55 PM Daniel Peebles wrote:
|   I think what you want is closed type families, as do I and many others :)
|   Unfortunately we don't have those.
|  
|  Closed type families wouldn't necessarily be injective, either. What he wants
|  is the facility to prove (or assert) to the compiler that a particualr type
|  family is in fact injective.
|  
|  It's something that I haven't really even seen developed much in fancy
|  dependently typed languages, though I've seen the idea before. That is: prove
|  things about your program and have the compiler take advantage of it.
|  
|  -- Dan
|  
|  ___
|  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


Deriviable type classes

2011-02-09 Thread Simon Peyton-Jones
Friends

Just a heads-up.  Pedro is working on implementing Generic Defaults, as 
described in his Haskell Symposium 2010 paper 
www.dreixel.net/research/pdf/gdmh_nocolor.pdf

It will replace (and improve on) the Derivable type classes stuff in GHC at 
the moment, which was originally presented in a paper of that title that Ralf 
and I wrote in the 2000 Haskell workshop 
http://research.microsoft.com/en-us/um/people/simonpj/papers/derive.htm.

The Derivable type class extension is barely used, I believe, and isn't even 
documented in the manual.  So I propose to switch from one to the other, rather 
than to try to support both.  This change will happen in GHC 7.2 or 7.4, 
depending on when Pedro is done.

Please yell if you are a secret user of derivable type classes, so this change 
would discombobulate you.

Simon


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


RE: Deriviable type classes

2011-02-09 Thread Simon Peyton-Jones
The Derivable type class extension is barely used, I believe, and isn't even 
documented in the manual.

Isn't it this?: 
http://www.haskell.org/ghc/docs/latest/html/users_guide/generic-classes.html

Oh yes, silly me.  It is documented!

Simon

From: José Pedro Magalhães [mailto:j...@cs.uu.nl]
Sent: 09 February 2011 12:20
To: Simon Peyton-Jones
Cc: GHC users
Subject: Re: Deriviable type classes

Hi,
2011/2/9 Simon Peyton-Jones 
simo...@microsoft.commailto:simo...@microsoft.com
Friends

Just a heads-up.  Pedro is working on implementing Generic Defaults, as 
described in his Haskell Symposium 2010 paper 
www.dreixel.net/research/pdf/gdmh_nocolor.pdfhttp://www.dreixel.net/research/pdf/gdmh_nocolor.pdf

It will replace (and improve on) the Derivable type classes stuff in GHC at 
the moment, which was originally presented in a paper of that title that Ralf 
and I wrote in the 2000 Haskell workshop 
http://research.microsoft.com/en-us/um/people/simonpj/papers/derive.htm.

The Derivable type class extension is barely used, I believe, and isn't even 
documented in the manual.

Isn't it this?: 
http://www.haskell.org/ghc/docs/latest/html/users_guide/generic-classes.html

But anyway, I can't remember seeing any use of it.


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


RE: Dictionaries and full laziness transformation

2011-02-09 Thread Simon Peyton-Jones
In general it's quite hard to solve this problem without risking losing sharing.

However in this case I added a simple arity analyser after the 7.0.1 release 
which solves the problem.  It'll be in 7.0.2.

Try with HEAD and check it does what you expect.

Simon

| -Original Message-
| From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-
| users-boun...@haskell.org] On Behalf Of Akio Takano
| Sent: 07 February 2011 04:10
| To: glasgow-haskell-users@haskell.org
| Subject: Dictionaries and full laziness transformation
| 
| Hi,
| 
| I'm using GHC 7.0.1. I found that recursive overloaded functions tend
| to leak memory when compiled with full-laziness optimization on. Here
| is a simple case.
| 
| -- TestSub.hs
| {-# LANGUAGE BangPatterns #-}
| module TestSub where
| 
| {-# NOINLINE factorial #-}
| factorial :: (Num a) = a - a - a
| factorial !n !acc = if n == 0 then acc else factorial (n - 1) (acc * n)
| 
| -- main.hs
| import TestSub
| 
| factorial1 :: Int - Int - Int
| factorial1 = factorial
| 
| main = do
| n - readLn
| print $ factorial1 n 1
| 
| main
| 
| This program should run in constant space, and compiled with -O0 or
| -O2 -fno-full-laziness, it does. However with -O2, it takes a linear
| amount of memory. The core for factorial looks like this:
| 
| TestSub.factorial =
|   \ (@ a_ajm) ($dNum_slz :: GHC.Num.Num a_ajm) -
| let {
|   a_slA :: GHC.Classes.Eq a_ajm
|   [LclId]
|   a_slA = GHC.Num.$p1Num @ a_ajm $dNum_slz } in
| let {
|   lvl2_slC :: a_ajm - a_ajm - a_ajm
|   [LclId]
|   lvl2_slC = TestSub.factorial @ a_ajm $dNum_slz } in
| ...
| 
| The problem is that lvl2_slC closure is created whenever factorial is
| applied to a Num dictionary, and kept alive until that application is
| GCed. In this program it never happens, because an application to the
| Num Int dictionary is referred to by the factorial1 CAF, and it
| recursively keeps the whole chain of closures alive.
| 
| I know that full laziness transformation *sometimes* causes a space
| leak, but this looks like a bad result to me, because:
| 
| - It looks like there is no point building a lot of equivalent
| closures, instead of one.
| - A lot of code can suffer from this behavior, because overloaded
| recursive functions are fairly common.
|   For example, unfoldConvStream function from the latest iteratee
| package suffers from this problem, if I understand correctly.
| 
| Does anyone have an idea on whether this can be fixed in GHC, or how
| to work around this problem?
| 
| Regards,
| 
| Takano Akio
| 
| ___
| 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: 4221 on new codegen

2011-02-03 Thread Simon Peyton-Jones
Correct.  The Cmm optimiser is supposed to make correctness preserving 
transformations.  The idea of the fuel is that you can binary chop your way 
to a situation where

Fuel = 0-143Program works
Fuel = 144  Program crashes

Then look at the single transformation that introduces the crash.

Well that's the intent anyway!

Simon

| -Original Message-
| From: ezyang [mailto:ezy...@mit.edu]
| Sent: 02 February 2011 23:12
| To: Simon Marlow; Simon Peyton-Jones
| Cc: glasgow-haskell-users
| Subject: Re: 4221 on new codegen
| 
| Simon Peyton Jones, I have a question about optimization fuel and GHC panics.
| When I vary the fuel using -dopt-fuel, I get the following varying behavior:
| 
| ...
| -dopt-fuel=144 = normal segfault (late in the program)
| -dopt-fuel=143 = segfaults ~immediately
| -dopt-fuel=142 = normal segfault
| -dopt-fuel=141 = fails an assert in file compiler/cmm/CmmBuildInfoTables.hs,
| line 128
| -dopt-fuel=140 = ditto
| -dopt-fuel=139 = resulting executable prints 'start' and then doesn't do
| anything
| ...
| 
| My impression was that these optimizations should not affect program
| behavior,
| in which case the first thing I should figure out is why -dopt-fuel results
| in
| the programming terminating after it prints 'start'. However, I'm not sure if
| this is a red herring. Am I on the right track?
| 
| Cheers,
| Edward
| 
| Quoting Simon Marlow marlo...@gmail.com:
| 
|  On 02/02/2011 00:29, Edward Z. Yang wrote:
|  More Hoopling later, I see this segment in the rewrite function:
| 
| middle m@(CmmUnsafeForeignCall _ fs _) live = return $
|   case map spill  (filter (flip elemRegSet (on_stack live)) fs) ++
|map reload (uniqSetToList (kill fs (in_regs live))) of
| []  -  Nothing
| reloads -  Just $ mkMiddles (m : reloads)
| 
|  So, if I understand this code correctly, it unilaterally reloads
|  /anything/ in the registers according to the analysis at that point.
| 
|  Well, I could see that resulting in the behavior below.
| 
|  It's not so clear to me what the correct rewrite is; according to
|  Marlow's comment on IRC, we ought not to be spilling/reloading foreign
|  calls yet, so maybe the whole bit should get excised? Otherwise, it seems
|  to me that transfer function needs to accomodate unsafe foreign
|  functions.
| 
|  Right, there's no need to spill/reload anything around an *unsafe*
|  foreign call in the Cmm code generator.  The NCG's register allocator
|  will do any necessary spilling/reloading around foreign calls.
| 
|  Cheers,
|  Simon
| 
| 
| 
|  Cheers,
|  Edward
| 
|  Excerpts from Simon Marlow's message of Tue Feb 01 03:44:41 -0500 2011:
|  On 01/02/2011 00:01, Edward Z. Yang wrote:
|  Current theory:
| 
|  c1jj:
|  _s1ep::I32 = I32[(slot_s1ep::I32   + 4)];   // CmmAssign
|  _s1fP::I32 = I32[(slot_s1fP::I32   + 4)];   // CmmAssign
|  // outOfLine should follow:
|  _s1eq::F64 = F64[_s1fP::I32 + 3];   // CmmAssign
|  I32[(youngc1jh   + 4)] = c1jh;   // CmmStore
|  foreign call ccall arg hints:  [PtrHint,]  result hints:
|   [] call_fn_blob(...) returns to c1jh args: ([_s1ep::I32,
| 
|_s1eq::F64]) ress:
|  ([_s1ev::F64]) with update frame 4;   // CmmForeignCall
|  c1jh:
|  _s1ev::F64 = F64[(slot_s1ev::F64   + 8)];   // CmmAssign
|  // emitReturn: Sequel: Assign
|  _s1ev::F64 = _s1ev::F64;   // CmmAssign
|  F64[(slot_s1ev::F64   + 8)] = _s1ev::F64;   // CmmStore
|  goto u1Ak;   // CmmBranch
| 
|  Note the line immediately after c1jh, where we reload the ostensibly
|  spilled _s1ev back into a register. Except that it was never spilled
|  there in the first place, and we just clobbered the real value. Oops.
| 
|  Is this interpretation correct?
| 
|  It sounds plausible, but I really have no idea.  The code generator does
|  not have to generate spill/reloads around foreign calls, the register
|  allocator will do that.
| 
|  Cheers,
|   Simon
| 
| 
| 
| 

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


RE: panic parsing a stmt in ghc 7 (possible regression?)

2011-02-01 Thread Simon Peyton-Jones
A panic is always a bug. Thanks for the test case.  I've created a ticket 
http://hackage.haskell.org/trac/ghc/ticket/4939

Simon

| -Original Message-
| From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-
| users-boun...@haskell.org] On Behalf Of Daniel Gorín
| Sent: 31 January 2011 21:56
| To: glasgow-haskell-users
| Subject: panic parsing a stmt in ghc 7 (possible regression?)
| 
| Hi
| 
| I'm trying to make the hint library work also with ghc 7 and I'm having
| problems with some test-cases that are now raising exceptions. I've been able
| to reduce the problem to a small example. The program below runs ghc in
| interpreter-mode and attempts to parse an statement using ghc's parseStmt
| function; the particular statement is a let-expression with a \n in the
| middle. The observed behaviour is:
| 
|  $ ghc-6.12.1 -fforce-recomp --make -package ghc -cpp -Wall d.hs  ./d
|  [1 of 1] Compiling Main ( d.hs, d.o )
|  Linking d ...
|  let {e = let x = ()
|  in x ;} in e
|  Ok
|  $ ghc-7.0.1 -fforce-recomp --make -package ghc -cpp -Wall d.hs  ./d
|  [1 of 1] Compiling Main ( d.hs, d.o )
|  Linking d ...
|  let {e = let x = ()
|  in x ;} in e
|  d: d: panic! (the 'impossible' happened)
|(GHC version 7.0.1 for i386-apple-darwin):
|  srcLocCol no location info
| 
|  Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug
| 
| Is it a regression or should I be doing this some other way?
| 
| Thanks,
| Daniel
| 
| -- d.hs
| import qualified GHC
| import qualified MonadUtils as GHC ( liftIO )
| import qualified StringBuffer as GHC
| import qualified Lexer as GHC
| import qualified Parser as GHC
| import qualified GHC.Paths
| 
| main :: IO ()
| main = GHC.runGhcT (Just GHC.Paths.libdir) $ do
|-- initialize
|df0 - GHC.getSessionDynFlags
|_ - GHC.setSessionDynFlags df0{GHC.ghcMode= GHC.CompManager,
|GHC.hscTarget  = GHC.HscInterpreted,
|GHC.ghcLink= GHC.LinkInMemory,
|GHC.verbosity  = 0}
|df1 - GHC.getSessionDynFlags
|   -- runParser
|let expr = let {e = let x = ()\nin x ;} in e
|GHC.liftIO $ putStrLn expr
|buf - GHC.liftIO $ GHC.stringToStringBuffer expr
|let p_res = GHC.unP GHC.parseStmt (mkPState df1 buf GHC.noSrcLoc)
|case  p_res of
|  GHC.POk{} - GHC.liftIO $ putStrLn Ok
|  GHC.PFailed{} - GHC.liftIO $ putStrLn Failed
| where
| #if __GLASGOW_HASKELL__ = 700
|   mkPState = GHC.mkPState
| #else
|   mkPState = \a b c - GHC.mkPState b c a
| #endif
| 
| 
| ___
| 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: Bug in undecidable instances?

2011-02-01 Thread Simon Peyton-Jones
You are misunderstanding what 'undecidable instances' does.

GHC wants to solve the constraint (D Foo beta) where beta is 
as-yet-unconstrained type variable.  It finds that one instance *matches* (by 
instantiating only the instance declaration, not the constraint we are solving):
D a b
but another instance *unifies*:
D Foo Foo
(That is, if 'beta' was later discovered to be 'Foo' then this latter instance 
would match.)  

Without undecidable instances, GHC will refrain from choosing either.  With 
undecidable instances, GHC chooses the one that matches (ie D a b) ignoring the 
possiblity that beta might later instantiate to Foo.

You want to unify beta with Foo, but that wouldn't work if there was another 
instances
D Foo Bar

That's the design at the moment.  If you are in undecidable-instance territory 
the ice is pretty thin.

Simon

| -Original Message-
| From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-
| users-boun...@haskell.org] On Behalf Of Roman Cheplyaka
| Sent: 31 January 2011 22:01
| To: glasgow-haskell-users@haskell.org
| Subject: Bug in undecidable instances?
| 
| The following looks like a bug in (undecidable) instances resolution.
| 
| {-# LANGUAGE
| MultiParamTypeClasses,FlexibleInstances,UndecidableInstances,
|  OverlappingInstances,IncoherentInstances #-}
| class C a b
| 
| instance C a (a,b)
| 
| class D a b
| 
| instance (D a b, C b c) = D a c
| 
| data Foo = Foo deriving Show
| data Bar = Bar deriving Show
| 
| instance D Foo Foo
| 
| c :: C x y = x - y - ()
| c _ _ = ()
| 
| d :: D x y = x - y - ()
| d _ _ = ()
| 
| 
| *Main d Foo Foo
| () -- as expected
| *Main c Foo (Foo,Bar)
| () -- as expected
| *Main d Foo (Foo,Bar)
| 
| interactive:1:1:
| Context reduction stack overflow; size = 21
| Use -fcontext-stack=N to increase stack size to N
|   [skip]
|   $dD :: D Foo b1
|   $dD :: D Foo b
|   $dD :: D Foo (Foo, Bar)
| In the expression: d Foo (Foo, Bar)
| In an equation for `it': it = d Foo (Foo, Bar)
| 
| I.e. for some reason on the second step resolver fails to pick up the
| most specific (and the most obvious) instance D Foo Foo and continues to
| apply the instance (D a b, C b c) = D a c.
| 
| Reproduced with GHC 6.12.1 and 7.0.1.
| 
| --
| Roman I. Cheplyaka :: http://ro-che.info/
| Don't worry what people think, they don't do it very often.
| 
| ___
| 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


FW: Problems with the directory package on windows

2011-01-31 Thread Simon Peyton-Jones
Friends

Can anyone help Tim with this?

Tim, it'd be a good idea to say what version of Cabal you are using (cabal 
--version).  Also you can download a pre-compiled cabal binary I believe, which 
would save you cabal-installing it.  (Although it seems bad that you can get 
into a situation where that's necesary.)

Simon

-Original Message-
From: Tim Sheard [mailto:she...@cs.pdx.edu] 
Sent: 28 January 2011 22:48
To: Simon Peyton-Jones
Subject: Problems with the directory package on windows

Simon,

I have been wrestling with following problem. I cannot get the Directory 
package to install on
windows.  Normally this comes with the Haskell Platform, but out of the 
box, it
gives an error message that it can't find the directory package, even 
though ghc-pkg says its there.
If you try and install it you get:

Resolving dependencies...
Downloading directory-1.1.0.0...
Configuring directory-1.1.0.0...
configure: WARNING: unrecognized options: --with-compiler
checking for gcc... gcc
checking whether the C compiler works... yes
checking for C compiler default output file name... a.exe
checking for suffix of executables... .exe
checking whether we are cross compiling... no
checking for suffix of object files... o
checking whether we are using the GNU C compiler... yes
checking whether gcc accepts -g... yes
checking for gcc option to accept ISO C89... none needed
checking how to run the C preprocessor... gcc -E
checking for grep that handles long lines and -e... /usr/bin/grep
checking for egrep... /usr/bin/grep -E
checking for ANSI C header files... yes
checking for sys/types.h... yes
checking for sys/stat.h... yes
checking for stdlib.h... yes
checking for string.h... yes
checking for memory.h... yes
checking for strings.h... yes
checking for inttypes.h... yes
checking for stdint.h... yes
checking for unistd.h... yes
checking for sys/types.h... (cached) yes
checking for unistd.h... (cached) yes
checking for sys/stat.h... (cached) yes
configure: creating ./config.status
config.status: creating include/HsDirectoryConfig.h
config.status: include/HsDirectoryConfig.h is unchanged
configure: WARNING: unrecognized options: --with-compiler
cabal.exe: Missing dependency on a foreign library:
* Missing header file: HsDirectory.h
This problem can usually be solved by installing the system package that
provides this library (you may need the -dev version). If the library is
already installed but in a non-standard location then you can use the flags
--extra-include-dirs= and --extra-lib-dirs= to specify where it is.
cabal.exe: Error: some packages failed to install:
directory-1.1.0.0 failed during the configure step. The exception was:
ExitFailure 1

Some one suggested I need to update cabal, but cabal needs directory so 
it won't update,
and both  cabal install cabal-install
   cabal install cabal
end in exactly the same kind of error.
Have you ever seen this problem. I have searched everywhere for similar 
questions
and have struggled several weeks with this.  Any suggestions.

Tim Sheard


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


RE: GHC 7.0.1 (or very strange dimensional-0.8.0.1) bug

2011-01-28 Thread Simon Peyton-Jones
Right; it's a bug all right.  Happily, I committed a major patch two weeks ago, 
which cures the bug (I checked). The fix will be in 7.0.2.  Meanwhile, if you 
can build the HEAD or get a development snapshot, you should be good to do.

Thanks for reporting this

Simon

From: glasgow-haskell-users-boun...@haskell.org 
[mailto:glasgow-haskell-users-boun...@haskell.org] On Behalf Of Pavel Perikov
Sent: 25 January 2011 19:44
To: Jeremy Shaw
Cc: glasgow-haskell-users@haskell.org
Subject: Re: GHC 7.0.1 (or very strange dimensional-0.8.0.1) bug

It is NOT type checking bug. It causes Rec {} in core and _|_ in runtime :)
On 25.01.2011, at 22:35, Jeremy Shaw wrote:


There is a weird type-checking bug in 7.0.1 that causes loopy behavior:

http://hackage.haskell.org/trac/ghc/ticket/4809

Not sure if that is what is happening to you or not. Though in my experience it 
did not actually print loop, it just hung.

- jeremy

On Jan 25, 2011, at 10:48 AM, Pavel Perikov wrote:



On 25.01.2011, at 18:37, Bjorn Buckwalter wrote:

(I
suspect the type inferencer is looping), but maybe you've figured out
something workable for you already.

I told you I'm exhausted right now, didn't I? :) This is definitely not type 
inferencer. The bug causes compiled program looping. And I have at least one 
case when let-trick fixes the behavior in compiled program.

Pavel.




Thanks,
Bjorn

(Sorry for the re-repost, Pavel, my incompetence is matched only by my
perseverance.)


On Tue, Jan 25, 2011 at 22:02, Pavel Perikov 
peri...@gmail.commailto:peri...@gmail.com wrote:
in ghci:
Prelude import Numeric.Units.Dimensional.Prelude as D
Prelude Numeric.Units.Dimensional.Prelude D.sqrt $ let s = 9 *~ (meter D.*
meter) in s
3.0 m
Prelude Numeric.Units.Dimensional.Prelude D.sqrt $ 9 *~ (meter D.* meter)
ghci hangs.
complied and optimized code detects loop and let-trick from the above
does not help.
Here's the complete ghci -v session which contains all package versions

ghci -v
GHCi, version 7.0.1: http://www.haskell.org/ghc/  :? for help
Glasgow Haskell Compiler, Version 7.0.1, for Haskell 98, stage 2 booted by
GHC version 6.12.3
Using binary package database:
/Library/Frameworks/GHC.framework/Versions/7.0.1-i386/usr/lib/ghc-7.0.1/package.conf.d/package.cache
Using binary package database:
/Users/pavel/.ghc/i386-darwin-7.0.1/package.conf.d/package.cache
hiding package containers-0.3.0.0 to avoid conflict with later version
containers-0.4.0.0
hiding package QuickCheck-2.3.0.2 to avoid conflict with later version
QuickCheck-2.4.0.1
wired-in package ghc-prim mapped to
ghc-prim-0.2.0.0-0713122c5f9038c6f0355a37e294e054
wired-in package integer-gmp mapped to
integer-gmp-0.2.0.2-bfb191b8468e4d812a2bb92622cb246e
wired-in package base mapped to
base-4.3.0.0-1ea085b64a078bd9d5eaa9d8d525e35e
wired-in package rts mapped to builtin_rts
wired-in package template-haskell mapped to
template-haskell-2.5.0.0-f262af1f92a427f5cf4133bff041044f
wired-in package dph-seq not found.
wired-in package dph-par not found.
Hsc static flags: -static
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
Loading package ffi-1.0 ... linking ... done.
Prelude import Numeric.Units.Dimensional.Prelude as D
hiding package containers-0.3.0.0 to avoid conflict with later version
containers-0.4.0.0
hiding package QuickCheck-2.3.0.2 to avoid conflict with later version
QuickCheck-2.4.0.1
wired-in package ghc-prim mapped to
ghc-prim-0.2.0.0-0713122c5f9038c6f0355a37e294e054
wired-in package integer-gmp mapped to
integer-gmp-0.2.0.2-bfb191b8468e4d812a2bb92622cb246e
wired-in package base mapped to
base-4.3.0.0-1ea085b64a078bd9d5eaa9d8d525e35e
wired-in package rts mapped to builtin_rts
wired-in package template-haskell mapped to
template-haskell-2.5.0.0-f262af1f92a427f5cf4133bff041044f
wired-in package dph-seq not found.
wired-in package dph-par not found.
*** Parser:
hiding package containers-0.3.0.0 to avoid conflict with later version
containers-0.4.0.0
hiding package QuickCheck-2.3.0.2 to avoid conflict with later version
QuickCheck-2.4.0.1
wired-in package ghc-prim mapped to
ghc-prim-0.2.0.0-0713122c5f9038c6f0355a37e294e054
wired-in package integer-gmp mapped to
integer-gmp-0.2.0.2-bfb191b8468e4d812a2bb92622cb246e
wired-in package base mapped to
base-4.3.0.0-1ea085b64a078bd9d5eaa9d8d525e35e
wired-in package rts mapped to builtin_rts
wired-in package template-haskell mapped to
template-haskell-2.5.0.0-f262af1f92a427f5cf4133bff041044f
wired-in package dph-seq not found.
wired-in package dph-par not found.
Prelude Numeric.Units.Dimensional.Prelude D.sqrt $ let s = 9 *~ (meter D.*
meter) in s
hiding package containers-0.3.0.0 to avoid conflict with later version
containers-0.4.0.0
hiding package QuickCheck-2.3.0.2 to avoid conflict with later version
QuickCheck-2.4.0.1
wired-in package ghc-prim mapped to
ghc-prim-0.2.0.0-0713122c5f9038c6f0355a37e294e054
wired-in package integer-gmp mapped to

RE: GHC 7.0.1 (or very strange dimensional-0.8.0.1) bug

2011-01-26 Thread Simon Peyton-Jones
I'm not certain, but I think so.

From: glasgow-haskell-users-boun...@haskell.org 
[mailto:glasgow-haskell-users-boun...@haskell.org] On Behalf Of Pavel Perikov
Sent: 26 January 2011 11:12
To: glasgow-haskell-users@haskell.org
Subject: RE: GHC 7.0.1 (or very strange dimensional-0.8.0.1) bug

Thanks, Simon!

Is the patch in the STABLE snapshot now?

pavel

On 26.01.2011, at 13:57, Simon Peyton-Jones wrote:


Right; it's a bug all right.  Happily, I committed a major patch two weeks ago, 
which cures the bug (I checked). The fix will be in 7.0.2.  Meanwhile, if you 
can build the HEAD or get a development snapshot, you should be good to do.

Thanks for reporting this

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


RE: Question about Haskell AST

2011-01-25 Thread Simon Peyton-Jones
My guess is that the base-package modules need language extensions to compile.  
These extensions are specified in libraries/base/base.cabal (search for 
extensions).  I don't think you are including these extensions in the dflags 
you are using.

Personally I think it'd be better if each base-package module specified its own 
extensions (using {-# LANGUAGE MagicHash #-} etc); then it'd be more 
self-describing.  But my (untested) guess is that you need to extend dflags 
with these extension flags to tell GHC how to compile them.

S

| -Original Message-
| From: Jane Ren [mailto:j2...@ucsd.edu]
| Sent: 24 January 2011 17:20
| To: Simon Peyton-Jones; glasgow-haskell-users@haskell.org
| Subject: RE: Question about Haskell AST
| 
| Hi Simon,
| 
| That is exactly what I needed.  However, although I was able to get the
| patterns from the parse tree for test modules that I wrote, I was not able to
| get the parsetrees for the Haskell base library modules.
| For example, I am trying to use Data/List.hs as a test.  Here's the code
| 
| defaultErrorHandler defaultDynFlags $ do
|   runGhc (Just libdir) $ do
| dflags - getSessionDynFlags
|   setSessionDynFlags dflags
| target - guessTarget targetFile Nothing
| setTargets [target]
| load LoadAllTargets
| modSum - getModSummary $ mkModuleName Data.List
| 
| When I try this, I get
| AstWalker: panic! (the 'impossible' happened)
|   (GHC version 7.0.1 for x86_64-apple-darwin):
|   lexical error at character 'i'
| 
| 
| It appears this error comes from load LoadAllTargets
| 
| Any ideas how I can get parse trees for the Haskell base modules?
| 
| Sure, I can augment that wiki page.
| 
| Thanks
| Jane
| 
| From: Simon Peyton-Jones [simo...@microsoft.com]
| Sent: Tuesday, January 11, 2011 12:06 AM
| To: Jane Ren; glasgow-haskell-users@haskell.org
| Subject: RE: Question about Haskell AST
| 
| desugarModule returns a GHC.DesugaredModule
| Inside a DesugaredModule is a field dm_core_module :: HscTypes.ModGuts
| Inside a ModGuts is a field mg_binds :: [CoreSyn.CoreBind]
| 
| And there are your bindings!  Does that tell you what you wanted to know?
| 
| Simon
| 
| PS: When you have it clear, would you like to augment the Wiki
| http://haskell.org/haskellwiki/GHC/As_a_library to describe what you learned?
| That way others can benefit.
| 
| | -Original Message-
| | From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-
| | users-boun...@haskell.org] On Behalf Of Jane Ren
| | Sent: 10 January 2011 17:21
| | To: glasgow-haskell-users@haskell.org
| | Subject: Question about Haskell AST
| |
| | Hi,
| |
| | I need to be able to take a piece of Haskell source code and get an
| | simplified, typed, intermediate representation of the AST, which means I
| need
| | to use compiler/coreSyn/CoreSyn.lhs
| |
| | So I'm first trying to get the desguaredModule of the source code with
| | ...
| | modSum - getModSummary $ mkModuleName ...
| | p - parseModule modSum
| | t - typecheckModule p
| | d - desugarModule t
| |
| | Now I'm really stuck on figuring out how to connect the variable d of type
| | desugaredModule to compiler/coreSyn/CoreSyn.lhs to get Expr patterns like
| | App, Let, Case, etc.
| |
| | Also, is it correct to get the deguaredModule first?  At least CoreSyn.lhs
| | seems to suggest this.
| |
| | Any suggestions would be greatly apprecia
| | ___
| | 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: backward compatibility

2011-01-21 Thread Simon Peyton-Jones
| So, again, for this particular extension I suggest that the layout
| rule in the standard(s) should be revised 

Indeed I suspect the NonDecreasingIndentation change is a proposal for Haskell 
Prime pocess.  Or if it isn't it could be is if someone proposed it.  That's 
the process we have in place for changing the base language.

Simon

| -Original Message-
| From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-
| users-boun...@haskell.org] On Behalf Of Axel Simon
| Sent: 20 January 2011 20:23
| To: Simon Marlow
| Cc: GHC users
| Subject: Re: backward compatibility
| 
| Hi Simon,
| 
| On Jan 20, 2011, at 17:54, Simon Marlow wrote:
| 
|  The layout fix is this change:
| 
| 
| http://hackage.haskell.org/trac/ghc/changeset/9a82b1ffa35fa4c3927c66a1037a37d
| 436cf6aac
| 
|  Another case where GHC was not strictly standards-compliant, and it
|  was fixed by adding a flag for the extension.
| 
| 
|  These were all bugs, but fixing them broke some code,
|  unfortunately.  In cases like this we *could* deprecate the
|  behaviour for one major release with a warning, before removing it.
|  However there's a non-trivial cost to doing so, and in some of these
|  cases it would have been quite awkward to implement the warning
|  (plus the cost of adding tests to make sure we actually got the
|  warning right; it's easy to introduce yet more bugs). Furthermore,
|  deprecations are often ignored, so sometimes the breakage is just
|  delayed.
| 
|  Hopefully that explains why sometimes we make breaking changes.  If
|  the breaking change has a high enough impact, then it becomes
|  worthwhile to add backwards compatibility (via warnings /
|  deprecation or whatever). Of course from the point of view of the
|  user, the impact is always either high (it broke) or zero (it
|  didn't) :-)  We have to make a judgement as to whether we should
|  spend effort on backwards compatibility or not.  Perhaps we're
|  getting it wrong - so feedback from users is always valuable.
| 
| I appreciate that you want to make ghc compliant to the standard. But
| to be honest, it is still the case that ghc defines the de-facto
| standard of what a Haskell program can be, since many programs do
| employ one or more ghc-only extensions.
| 
| In the case of the layout bug, I think it might be worth considering
| going the other way: adjusting the standard with what ghc has always
| done. If I understand correctly, all my code using:
| 
| foo = do
|some computation
|trace I am here $ do
|some more computation
| 
| will break. I use this style of coding a lot to avoid too much
| indentation and thus I would have to enable this extension everywhere
| (and get warnings (or errors?) for older ghcs). Even if we had 2 or 3
| implementations of Haskell 2010 in a decade, then they might not have
| this extension. Furthermore, if they claim they actually do implement
| the layout extension then they still might get it wrong in some subtle
| way. An extension is never as well exercised as the non-extension part
| of the compiler. I therefore think that keeping the number of
| extensions to a minimum should be a high priority. It seems that the
| ghc team is going overboard with the amount of extensions and their
| granularity that I do not believe that there will ever be another
| compiler since implementing all these extensions is a nightmare. The
| road of may extensions is leading down the road that the Haskell
| standards aimed to avoid: having a single implementation defining what
| a Haskell program can be.
| 
| So, again, for this particular extension I suggest that the layout
| rule in the standard(s) should be revised -- if I'm mistaken, this
| will not break other programs.
| 
| Cheers,
| Axel
| 
| 
| ___
| 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: Release/git plans

2011-01-21 Thread Simon Peyton-Jones
Austin

| So, given that 7.2 will be released much earlier than the normal
| release cycle, is there any room for anything else to get into HEAD
| for the 7.2 release before everything is switched? In particular I
| fixed up Max Bolingbroke's old compiler plugin work to be usable with
| the latest HEAD, and all the fundamental work is there and done, just
| some additional small things are needed (notably having ghc dump
| plugin information a la -ddump flags, and testsuite patches are about
| it I think.) The patch itself is pretty small and doesn't touch *too*
| much code, mostly adding dynamic loading and the plugin API, but it's
| arguably adding a 'big' feature for users of GHC to start utilizing,
| and perhaps a release in 7.2 would cause problems merging changes
| until you cut a new STABLE branch with git, like you said.

I'm sorry I've been slow on this.  Review and apply the plugins patch is in 
my inbox, but it's been queued up behind too many other things, notably making 
the new typechecker work.

I'm pretty keen on the whole plugin idea, because it makes the compiler more 
extensible and lowers the barrier to entry.  My only reason for delay is that I 
wanted to review the design (as seen by a plug-in author).  Once we provide it, 
we have to support it, and it's harder to change.

The fact that you are actively engaged, have done the work with Max, and are (I 
assume) happy to respond to user queries, fix bugs etc, is a major incentive.  
Thank you!

So yes, because of that I undertake to do this for 7.2 [unless Simon M tells me 
no :-)].  I'll add a few thoughts to the ticket right now.  
http://hackage.haskell.org/trac/ghc/ticket/3843.  Interested parties, add 
yourselves to the cc list of the ticket.

Simon


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


RE: backward compatibility

2011-01-21 Thread Simon Peyton-Jones
| You've convinced me.  The benefit from fixing GHC in this case is
| outweighed by the cost, I think we should revert the change (or at least
| enable RelaxedLayout by default), and propose the change for Haskell
| 2011/2012.  Ian, Simon, what do you think?

I'm ok with that

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


RE: Question about Haskell AST

2011-01-11 Thread Simon Peyton-Jones
desugarModule returns a GHC.DesugaredModule
Inside a DesugaredModule is a field dm_core_module :: HscTypes.ModGuts
Inside a ModGuts is a field mg_binds :: [CoreSyn.CoreBind]

And there are your bindings!  Does that tell you what you wanted to know?

Simon

PS: When you have it clear, would you like to augment the Wiki 
http://haskell.org/haskellwiki/GHC/As_a_library to describe what you learned?  
That way others can benefit.

| -Original Message-
| From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-
| users-boun...@haskell.org] On Behalf Of Jane Ren
| Sent: 10 January 2011 17:21
| To: glasgow-haskell-users@haskell.org
| Subject: Question about Haskell AST
| 
| Hi,
| 
| I need to be able to take a piece of Haskell source code and get an
| simplified, typed, intermediate representation of the AST, which means I need
| to use compiler/coreSyn/CoreSyn.lhs
| 
| So I'm first trying to get the desguaredModule of the source code with
| ...
| modSum - getModSummary $ mkModuleName ...
| p - parseModule modSum
| t - typecheckModule p
| d - desugarModule t
| 
| Now I'm really stuck on figuring out how to connect the variable d of type
| desugaredModule to compiler/coreSyn/CoreSyn.lhs to get Expr patterns like
| App, Let, Case, etc.
| 
| Also, is it correct to get the deguaredModule first?  At least CoreSyn.lhs
| seems to suggest this.
| 
| Any suggestions would be greatly apprecia
| ___
| 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: Type families status

2010-12-13 Thread Simon Peyton-Jones
Yes, I think type families are here to stay.

There is no formal policy about GHC extensions.  Generally speaking, I regard 
GHC as a laboratory in which to test ideas, which militates in favour of 
putting things in so that people can try them.  Once in they are hard to take 
out again (linear implicit parameters is a rare exception) because some come to 
rely on them.

If there's anything in particular you need, ask.  The main thing that is 
scheduled for an overhaul is the derivable type class mechanism, for which 
Pedro is working on a replacemement.

Simon

| -Original Message-
| From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-
| users-boun...@haskell.org] On Behalf Of Permjacov Evgeniy
| Sent: 10 December 2010 19:42
| To: glasgow-haskell-users@haskell.org
| Subject: Type families status
| 
| Is it safe to consider type families and associated type families
| extensions for ghc as stable ? Wich related extensions (flexible
| contexts, undecidable instanses and so on) may be deprecated or changed
| in near (2-3 years) future and wich may not?
| 
| ___
| 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: MonoLocalBinds and hoopl

2010-12-10 Thread Simon Peyton-Jones
Yes, argument to higher rank functions are probably the top reason why 
MonoLocalBinds is a nuisance.  

As of now I think the best thing is to do (1), but define type synonyms that 
abbreviate the oft-repeated signatures. That should make the signatures much 
onerous.

Simon

| -Original Message-
| From: Edward Z. Yang [mailto:ezy...@mit.edu]
| Sent: 09 December 2010 15:28
| To: glasgow-haskell-users; Simon Peyton-Jones
| Subject: MonoLocalBinds and hoopl
| 
| Hello all,
| 
| Here's an experience report for porting hoopl to manage MonoLocalBinds.  The
| Compiler.Hoop.XUtil module has a rather interesting (but probably common)
| style of code
| writing, along the lines of this:
| 
| fbnf3 (ff, fm, fl) block = unFF3 $ scottFoldBlock (ScottBlock f m l cat)
| block
| where f n = FF3 $ ff n
|   m n = FF3 $ fm n
|   l n = FF3 $ fl n
|   FF3 f `cat` FF3 f' = FF3 $ f' . f
| 
| f, m, l and cat are polymorphic functions that are only used once in the
| main expression, and are floated outside to improve readability.  However,
| when
| MonoLocalBinds is turned on, these all become monomorphic and the definitions
| fail.  In contrast, this (uglier) version typechecks:
| 
| fbnf3 (ff, fm, fl) block = unFF3 $ scottFoldBlock (ScottBlock (FF3 . ff) (FF3
| . fm) (FF3 . fl) (\(FF3 f) (FF3 f') - FF3 $ f' . f)) block
| 
| One suggestion that I had was that we should generalize local bindings that
| are only used once, but Marlow pointed out that this would make the
| typechecker
| more complex and I probably would agree.
| 
| As a userspace developer, I have two options:
| 
| 1. Bite the bullet and put in the polymorphic type signatures (which
|can be quite hefty)
| 2. Inline the definitions
| 3. Move the polymorphic functions into the global namespace
| 
| (3) and (2) are not so nice because it breaks the nice symmetry between these
| definitions, which always define f, m, l for the many, many definitions in
| Hoopl of this style.
| 
| Cheers,
| Edward

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


RE: [darcs-users] How to develop on a (GHC) branch with darcs

2010-12-09 Thread Simon Peyton-Jones
| thoroughly exhausted. Even when Darcs was in a far
| less advanced state than it is in now, the conclusion seemed
| to be that the best interests of the Haskell community at
| large are served by remaining with Darcs. So it would be a bit
| strange if this branching issue, which is a serious issue
| currently but will likely become a non-issue in a few months time,
| triggers GHC to abandon Darcs.

Let's not go overboard here.  Iavor was expressing his frustration with using 
Darcs, and that is useful information for the Darcs devs to have, so they know 
where to focus their efforts.  Already this thread has generated new useful 
information.  For example, Iavor knows about --skip-conflicts, and I know that 
things might be better in months not years.  Neither of us knew those things 
before.

For GHC, we have two strong incentives to stick with Darcs.  First, we use it 
at the moment and there'd be a lot of hoo-ha to change.  Second, Darcs is 
written by people in our community, and GHC is a big customer, so I for one 
am keen to be supportive.

But we don't want to discourage people who'd like to help with GHC either.  For 
example, here is one response to the thread, from Tim Middleton:

| For the record, I can say that as a Haskell fan and someone who's using 
| Haskell at work (for small tools and projects), and as someone who'd like 
| to contribute to GHC (especially to the cross-compiler effort), having to 
| work with darcs is a very frustrating. 

The more everyone can do to understand what the frustration is, and to describe 
workflows that make it as easy as possible, the better.

Simon

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


RE: [darcs-users] How to develop on a (GHC) branch with darcs

2010-12-08 Thread Simon Peyton-Jones
| known problem with darcs with no obvious solution.  For me, switching
| GHC to git would certainly be a win.

I have personal experience of git, because I co-author papers with git users. I 
am not very technologically savvy, but my failure rate with git is close to 
100%.  Ie I can do the equivalent of 'pull' or 'push' but I fail at everything 
else with an incomprehensible error message.  Maybe I just need practice (or 
more diligence), but I really don't understand git's underlying model, despite 
trying, and reading several tutorials.  If anyone has a favourite how to 
understand git doc, do point me at it.

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


<    1   2   3   4   5   6   7   8   9   10   >