: 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
| tcEx
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
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 ::
but if you write
g ::
g = f
the program is rejected. Sounds similar to what you are seeing. Look
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] Polymorphi
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-use
| 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.
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,
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-user
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 injectiv
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
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 w
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
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
mailto:simo...@microsoft.com>>
Friends
Just a heads-up. Pedro is working on implementing "Generic Defaults", as
described
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
oduces 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
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
bu
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: 3
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
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-
Yes, that's wrong. Thank you. Now fixed; see
http://hackage.haskell.org/trac/ghc/ticket/4918
Simon
From: glasgow-haskell-users-boun...@haskell.org
[mailto:glasgow-haskell-users-boun...@haskell.org] On Behalf Of José Pedro
Magalhães
Sent: 18 January 2011 10:33
To: GHC users
Subject: Behavior o
) 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 HEA
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
| 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
___
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
| 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 p
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
Try GHC.getNamesInScope, which will give you all the entities in scope.
Then use GHC.lookupName to see what manner of beast the Name is bound to (an
Id, Class, TyCon etc)
Does that help?
Simon
| -Original Message-
| From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell
Yes, it's a bug all right. See http://hackage.haskell.org/trac/ghc/ticket/4846
Thanks
Simon
| -Original Message-
| From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-
| users-boun...@haskell.org] On Behalf Of Emil Axelsson
| Sent: 16 December 2010 13:26
| To: glasg
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 i
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 m
| 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 issu
| 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 equiva
I too wish there was a good solution here. I've taken to making dated repos,
thus
http://darcs.haskell.org/ghc-new-co-17Nov10
When it becomes unusable, I make a brand new repo, with a new date starting
from HEAD, pull all the old patches, unrecord them all, rerecord a mega-patch,
and co
I think it would help to separate issues.
If it were not for rebindable syntax, there would be no need for these "op"
fields in (say) BindStmt etc. Instead, we'd have a fixed typing rule for
BindStmt, and the desugarer would use the fixed Control.Monad.(>>=). The
rebindable syntax thing just
read the QML paper! that's the trick. simpler, but with a heavier annotation
burden than the more sophisticated approaches
| -Original Message-
| From: Gregory Crosswhite [mailto:gcr...@phys.washington.edu]
| Sent: 19 November 2010 19:59
| To: Simon Peyton-Jones
| Cc: Haskell
Yes, impredicative types are still in, but in a simpler form than before, along
the lines of QML
http://research.microsoft.com/en-us/um/people/crusso/qml/
I have been too busy with getting the new type checker working to describe or
document it. Notably, I have not yet added syntax for QML's ri
I'm trying to give the user the possibility to jump to the definition of a
symbol in the source file. You click on the name of a function and you're send
to the module where it's defined. So I have an AST, and somewhere down the line
I have an Id object representing that function call. Then I ju
Interesting. What would it look like in Core? Anyone care to make a ticket?
S
| -Original Message-
| From: glasgow-haskell-users-boun...@haskell.org
[mailto:glasgow-haskell-users-
| boun...@haskell.org] On Behalf Of Roman Leshchinskiy
| Sent: 03 November 2010 10:55
| To: Christian
| > Well, I'm aware that it's a compromise. I don't know how to do a bang-up
principled
| job of typechecking local polymorphism, so GHC does a best-effort job. In
fact best
| effort is pretty good, and it's not hard to implement, so
| >a) I don't expect to remove NoLocalMonoBinds
| >
| > Make sure you are using RC2 of the compiler, from what I remember RC1
| > required signatures it shouldn't have, or enabled MonoLocalBinds more
| > than it should - RC2 required less signatures. However, your code
| > could well just be heavily using the relevant features.
|
| I was usin
.dijk@gmail.com]
| Sent: 30 October 2010 00:58
| To: glasgow-haskell-users@haskell.org
| Cc: Simon Peyton-Jones
| Subject: Re: Type error in GHC-7 but not in GHC-6.12.3
|
| On Fri, Oct 29, 2010 at 5:42 PM, Simon Peyton-Jones
| wrote:
| > That looks odd.
| >
| > Can you isolate
why you encountered the puzzling behaviour you describe below.
Simon
| -Original Message-
| From: Bas van Dijk [mailto:v.dijk@gmail.com]
| Sent: 30 October 2010 21:14
| To: glasgow-haskell-users@haskell.org
| Cc: Simon Peyton-Jones
| Subject: Re: Type error in GHC-7 but not in GHC-6.
| > | On a related note, these are also apparently allowed (in 6.10.4):
| > | f :: forall a. (Eq a => a -> a) -> a -> a
| > | -- the Eq context prevents the function from ever being called.
| >
| > That's not true. E.g.
| > f ((==) True) True
| > works fine.
|
| What I meant is that
Sent: 22 October 2010 19:50
To: Simon Peyton-Jones
Cc: glasgow-haskell-users@haskell.org
Subject: Re: context-stack GHC 7.0.1 Release Candidate 1
I was running into a similar issue and haven't noticed a dramatic improvement
with the latest changes. The number of ticks taken to compile are app
| On a related note, these are also apparently allowed (in 6.10.4):
| f :: forall a. (Eq a => a -> a) -> a -> a
|-- the Eq context prevents the function from ever being called.
That's not true. E.g.
f ((==) True) True
works fine.
|g :: forall a. Ord a => (Eq a => a -> a) -> a
| >An implicit quantification point is
| > a) the type in a type signature f :: type or
| > b) a type of the form (context => type)
| >if it does not start with an explicit 'forall'
|
...
| How inconvenient would it be to make the above description simpler by
| dropping b) and th
| > In a data type decl
| >data Foo = Foo (Eq a => a)
| > the "top of the type" is done separately for each argument. After
| > all, Foo (Eq a => a) isn't a type. So you get
| >data Foo = Foo (forall a. Eq a => a)
|
| This was a surprise as
|
| data Bar = Bar (a -> a)
|
| is illeg
The current story is this:
GHC adds an implicit "forall" at the top of every type
that foralls all the type variables mentioned in the type
that are not already in scope (if lexically scoped tyvars is on)
This is stated pretty clearly here
http://www.haskell.org/ghc/docs/6.12.2/html/use
| Sent: 12 October 2010 12:47
| To: Simon Peyton-Jones
| Cc: glasgow-haskell-users@haskell.org
| Subject: Re: context-stack GHC 7.0.1 Release Candidate 1
|
| Am 08.10.2010 18:52, schrieb Simon Peyton-Jones:
| > Christian
| >
| > We've committed a wave of patches that should substantial
Folks
Following lots of feedback from users, especially at ICFP, I've evolved some
proposals for Template Haskell, that should make it both more expressive, and
more secure.
http://hackage.haskell.org/trac/ghc/blog/Template%20Haskell%20Proposal
Do let me know what you think. Discussion by ema
Thanks. We knew about this -- in flight changes happening now -- but I've
added it as a new regression test even so.
Simon
| -Original Message-
| From: Christian Maeder [mailto:christian.mae...@dfki.de]
| Sent: 15 October 2010 17:53
| To: GHC Users Mailing List
| Cc: Simon Peyton-
| Now that the Glorious New type checker can handle local evidence
| seamlessly, is it a big implementation burden to extend it to deal
| with local *type class instances* in addition to local *equality
| constraints*?
...
| Are there big theoretical problems with this extension, or is it just
| a
Which version of GHC are you using? GHC 6.12 does not complain about unused
variables bound by "..". Try this, which complains about y, but not g.
Simon
{-# LANGUAGE RecordWildCards #-}
module Test where
data T = MkT { f,g :: Int }
p (MkT { .. }) y = f
| -Original Message-
| From
Christian
We've committed a wave of patches that should substantially improve the
typechecker. Could you try with the current HEAD?
(Or you can wait for the next release candidate, end next week; but sooner is
better.)
Simon
| -Original Message-
| From: glasgow-haskell-users-boun...@
Good idea. I've made a new Trac ticket and responded there. I suggest that
others do the same, so the conversation is captured in the ticket.
http://hackage.haskell.org/trac/ghc/ticket/4370
You can add yourself to the cc list of the ticket to stay in the loop.
Of course, do use the mailing list
: Simon Peyton-Jones
| Cc: glasgow-haskell-users@haskell.org
| Subject: Re: GHC 7.0.1 rc1: Could not deduce (Typeable a) from the context
(Typeable
| a, …)
|
| Simon Peyton-Jones wrote:
| > Oh dear, that really is quite a strange error message. Something is
| > definitely wrong. C
| Except I don't know how to write a type signature for this.
|
| The value 's' passed in is bound by pattern matching on this guy's
constructor:
|
| data Stream a = forall s. Stream (s -> Step s a) !s Int
|
| in the top-level function, so I don't even know if it has a type I can name.
| (2) ghc-6.12.2 compiles docon-2.11
| (download it via http://haskell.org/ghc/docon/
| and follow install.txt
| )
I get "Not found" when following http://haskell.org/ghc/docon
Simon
___
Glasgow-haskell-users mailing list
Glasgow-ha
Oh dear, that really is quite a strange error message. Something is definitely
wrong. Can you please make a ticket for it, and include instructions on how to
reproduce it?I gather that it depends on other packages that themselves
needed changes, so reproduction might not be entirely easy?
S
| Here's a boiled-down equivalent to what the issue is in uvector:
|
| http://hpaste.org/40213/doesnt_work_in_ghc_7
|
| In GHC 6.12, this would have type-checked. In GHC 7, I need to add a
| type-signature to the 'helper' function, except I 'm not sure how to
| do it.
|
| So the functio
kell-users-boun...@haskell.org
[mailto:glasgow-haskell-users-
| boun...@haskell.org] On Behalf Of Don Stewart
| Sent: 29 September 2010 14:53
| To: Simon Peyton-Jones
| Cc: glasgow-haskell-users@haskell.org
| Subject: Re: ANNOUNCE: GHC 7.0.1 Release Candidate 1
|
| I've created a wiki pa
I've been meaning to write a blog post about this, because it's a significant
change. I'll do this when I get home after ICFP. Briefly though:
* If you use -XGADTs or -XTypeFamilies (or -fglasgow-exts, which is deprecated)
you get -XMonoLocalBinds, which says that local let/where bindings are
We found another occurrence of very poor performance in a smaller program. We
have a nice fix; but won't be able to commit for a few days
Let's hope it fixes your problem too!
Simon
| -Original Message-
| From: glasgow-haskell-users-boun...@haskell.org
[mailto:glasgow-haskell-users-
| For patterns in left hand sides (lhs) of let or where also no warnings
| are issued.
|
| data Foo = Bar Int | Baz
|
| test3 :: Foo -> Int
| test3 x = let Bar i = x in i
|
| Will or should these cases be covered, too?
No, I don't plan to warn about these, which is the case at present. It's qu
Good point. Simon and I have decided we agree. I'll push a patch shortly.
S
| -Original Message-
| From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-
| users-boun...@haskell.org] On Behalf Of Mitar
| Sent: 21 September 2010 07:44
| To: glasgow-haskell-users
| Subjec
Don't I need to work on LHsExpr rather than HsExpr? How would I otherwise get
the location?
Yes, indeed, LHsExpr.
*Binding> getExpr (Lam v e) = g_del v (getExpr g e)
I still don't quite the purpose of this
Well if you have (\x -> y + x) there is a free occurrence of 'y' but
It probably is linked if you use --make, but should not be if you use an
explicit link command
ghc -o run-me A.o B.o C.o
Just omit LargeThModule.o
Hmm. Maybe this won't work, because there is a module initialisation tree, in
which each module calls the initialisation function of the mo
I found the spot where the collected RdrNames are used to generate the unused
import warnings, but I don't quite understand where they are gathered. Is there
an AST traversal function somewhere that gathers these RdrNames? If so, I could
use it as a blue print to write my own traversal.
No, it
Johan
GHC already collects all RdrNames for imported things, for use when reporting
unused imports. But it doesn't collect the SrcSpan of the occurrences, nor
does it collect occurrences of locally-bound things.
I suggest you write a general traversal looking like
data Gather var res
= Gat
| > I'm afraid I didn't understand your questions well enough to answer them.
|
| My question is, why does this type check:
It's hard for me to answer a question like that! To explain why something type
checks I'd have to show every constraint and how it is solved.
I think you have something
| > ghc-6.12.3:
| > 89,330,672 bytes allocated in the heap
| > 15,092 bytes copied during GC
| > 35,980 bytes maximum residency (1 sample(s))
| > 29,556 bytes maximum slop
| >2 MB total memory in use (0 MB lost due to fragmentation)
| >
|
Mitar
I'm afraid I didn't understand your questions well enough to answer them. But
it'd be worth reading
http://www.haskell.org/ghc/docs/6.12.2/html/users_guide/other-type-extensions.html#scoped-type-variables
| > It's not trivial to add, but not really hard either. Has anyone else been
| bi
Mitar, and others
Yes, I've spent most of the last month working on the new type checker, and
unless there's a major hiccup it'll be in GHC 7.0. We'll produce a release
candidate just before ICFP.
However, as it happens both your tests compile with GHC 6.12, if you add
ScopedTypeVariables. T
Doesn't look right. I've made a ticket
http://hackage.haskell.org/trac/ghc/ticket/4283
Simon
| -Original Message-
| From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-
| users-boun...@haskell.org] On Behalf Of Mitar
| Sent: 02 September 2010 01:27
| To: glasg
It's a bit of a moveable feast. With -fno-spec-constr-count you allow GHC to
specialise as much as it pleases, which is good for perf (maybe) but can lead
to major code size expansion.
S
From: Johan Tibell [mailto:johan.tib...@gmail.com]
Sent: 31 August 2010 10:16
To: Simon Peyton-Jon
I can’t reproduce this. With the enclosed module and HEAD, I get the warning;
but when I add –fspec-constr-count=5, the warning goes away and I get the
specialised rules.
Could Cabal not be passing on the flag or something?
Simon
module Foo where
data T = A | B | C | D | E
f :: T -> [Bool]
Kathleen
I talked to Simon. We are puzzled. Maybe a file has moved, so that make
maintainer-clean isn't cleaning it. (That's something the build system is bad
about.)
Can you try in a completely fresh tree? And, if that fails, send (a url to)
the entire build log?
Incidentally cvs-...@has
It's hard to read your code because the line breaks have been removed.
Moreover I think your code depends on some unspecified Hackage package. And I
couldn't find the enclosed Core dumps. Nor do you specify which version of GHC
you are using.
Still I believe that the nub is this. You have a
Sorry, my fault. Simon M is fixing
S
From: glasgow-haskell-users-boun...@haskell.org
[mailto:glasgow-haskell-users-boun...@haskell.org] On Behalf Of Johan Tibell
Sent: 26 August 2010 09:08
To: glasgow-haskell-users
Subject: HEAD unbuildable
I'm having trouble building HEAD, to the point where e
Data constructor workers don't have bindings: they just stand for themselves.
Wrappers do have bindings, but the easiest way to get them is to get them and
ask for their unfolding (via unfoldingTemplate . idUnfolding).
So you just need to get the Ids. You can get them from the global type
enviro
| {-# LANGUAGE GADTs #-}
| module Foo where
|
| data TemplateValue t where
| TemplateList :: [x] -> TemplateValue [x]
|
| instance (Eq b) => Eq (TemplateValue b) where
| (==) (TemplateList p) (TemplateList q) = (==) p q
A good example. Yes, GHC 6.12 fails on this and will always fail becau
Dear TH users
In Template Haskell, it's not currently possible to say "give me all the
instances of this class"; it's a long-standing feature request.
Sam Anklesaria has come up with a design and implemented it. Before committing
to it, I want to check that other Template Haskell users are happ
You don't want to go overboard here.
1. You *want* a distinct blob of lookup code for each different key type,
because you really do want a different lookup structure for each
2. For the most part you *dont want* a different blob of lookup code for
each value type, because almost al
| SPECIALISE pragmas are not supported in any but the defining module
| because the Core for a function to specialise is not guaranteed to be
| available in any other module. I don't think there is any other
| barrier.
Yes, exactly.
| It is possible to imagine implementing a remedy for this by us
| Knowing that, I'd like to be able to resolve (Show a, Monad m) as
| (Show [Char], Monad IO). Put more simply, I'd like the applyInst
| expression to typecheck as the apply expression does. Reading through
| the OutsideIn paper over the weekend, I began to understand why it
| isn't so simple. I
Matt
I afraid I didn't understand your email well enough to offer a coherent
response. For example I have no clue what "instance unifs" might mean. Nor do
I understand what your program seeks to achieve.
Thomas is right to say that the type checker is in upheaval at the moment. I'm
activel
ly 2010 17:46
To: Simon Peyton-Jones
Cc: glasgow-haskell-users@haskell.org
Subject: Re: Casting + eta reduction
Or a different way:
I want -fdo-lambda-eta-expansion (which, if I understand correctly, actually
triggers eta *reduction*) to eliminate argument casts, as well.
My motivation: I'
It compiles to
lift f d = f (d `cast` blah)
which seems fine to me. Are you unhappy with that?
Simon
From: glasgow-haskell-users-boun...@haskell.org
[mailto:glasgow-haskell-users-boun...@haskell.org] On Behalf Of Louis Wasserman
Sent: 09 July 2010 03:30
To: glasgow-haskell-users@haskell.org
S
| The head has -dsuppress-coercions which omits coercion terms when pretty
| printing Core. It would be easy to backport that to 6.12.
The HEAD also has a coercion optimiser that dramatically shrinks some large
coercion terms.
| > I might revert both mwc-random and statistics back to using plain
Thank you! I am utterly buried just now (POPL) but will get to this.
Simon
From: glasgow-haskell-users-boun...@haskell.org
[mailto:glasgow-haskell-users-boun...@haskell.org] On Behalf Of Bryan O'Sullivan
Sent: 12 July 2010 13:58
To: Simon Peyton-Jones
Cc: glasgow-haskell-users@haskel
]
| Sent: 12 July 2010 01:56
| To: Simon Peyton-Jones
| Cc: glasgow-haskell-users@haskell.org
| Subject: Re: Massive slowdown in mwc-random after switching to use of
| primitive package
|
| On Sunday 11 July 2010 1:31:23 pm Simon Peyton-Jones wrote:
| > This is the first I've heard of this.
| > caused a huge performance regression.
|
| You're using GHC 6.12.x presumably? There are known performance problems with
| using abstract PrimMonads in that version (and, actually, just using IO as
| well).
...
| The good news is that, last I checked, this isn't a problem in HEAD. The
|
| Here's a concrete case I recently ran into:
|
| type family SomeOtherTypeFamily a
| class SomeClass a where type SomeType a
| instance a ~ SomeOtherTypeFamily b => SomeClass a where
|type SomeType a = (b,Int)
|-- (error) Not in scope: type variable `b'
|
| The same thing
Robert
Great example! Your test case makes the type checker work hard to produce
solve the type-equality constraints (and you have a lot of them); when
pretty-printed it comes to 7000 lines! But these large proofs are readily
simplified to something tiny, just a few lines.
As luck would have
There have been a couple of emails about Template Haskell support for
· GADTs
· View patterns
· Reifying instances
There’s a ticket for this already
http://hackage.haskell.org/trac/ghc/ticket/3497
It’s mainly a library design question, in this case the design of the Te
See my comment http://hackage.haskell.org/trac/ghc/ticket/4028#comment:4
Simon
| -Original Message-
| From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-users-
| boun...@haskell.org] On Behalf Of Seyed Hosein Attarzadeh Niaki
| Sent: 27 April 2010 20:41
| To: glasgow-
It's a bug, but it's been fixed
http://hackage.haskell.org/trac/ghc/ticket/3833
Thakns
Simon
| -Original Message-
| From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-
| users-boun...@haskell.org] On Behalf Of Ben
| Sent: 04 May 2010 06:55
| To: glasgow-haskell-users
| Does this mean DPH is ready for abuse?
|
| The wiki page sounds pretty tentative, but it looks like it's been awhile
| since it's been updated.
|
| http://www.haskell.org/haskellwiki/GHC/Data_Parallel_Haskell
In truth, nested data parallelism has taken longer than we'd hoped to be ready
for a
| Again, my question is: suppose the following code is given:
|
| module Test (R(..)) where
| data R = R { x :: Char, y :: Int, z :: Float }
|
| and ":browse" of GHC 6.12 displays:
|
| data R = R {x :: Char, y :: Int, z :: Float}
| data R = R {x :: Char, ...}
| data R = R {..., y :: Int, ...}
|
| >> I compiled my code with -fdicts-strict.
| >
| > What is this actually supposed to do? It seems the documentation is
| missing:
| > http://www.haskell.org/ghc/docs/latest/html/users_guide/options-
| optimise.html#options-f
|
| >From reading the source code, it appears to make any dictionary fi
401 - 500 of 1599 matches
Mail list logo