Re: Why aren't classes like "Num" levity polymorphic?

2022-05-09 Thread Edward Kmett
Another, weaker version of this is to just require default signatures that assume r has type LiftedRep for each of the defaults, but then instantiating things at obscure kinds becomes _much_ harder. -Edward On Mon, May 9, 2022 at 12:30 PM Edward Kmett wrote: > Also, if you do want

Re: Why aren't classes like "Num" levity polymorphic?

2022-05-09 Thread Edward Kmett
s to access that functionality. You can also use the new UnliftedDataTypes and/or UnliftedNewtypes to do things like pass around a Natural# that is stored in a couple of registers and then build support for it. This is also included in that repo above. -Edward On Mon, May 9, 2022 at 12:24

Re: Why aren't classes like "Num" levity polymorphic?

2022-05-09 Thread Edward Kmett
It is rather shockingly difficult to get it to work out because of the default definitions in each class. Consider just class Eq (a :: TYPE r) where (==), (/=) :: a -> a -> Bool That looks good until you remember that x == y = not (x /= y) x /= y = not (x == y) are also included in the c

Re: Pattern synonym constraints :: Ord a => () => ...

2021-10-05 Thread Edward Kmett
On Tue, Oct 5, 2021 at 12:39 PM David Feuer wrote: > To be clear, the proposal to allow different constraints was accepted, but > integrating it into the current, incredibly complex, code was well beyond > the limited abilities of the one person who made an attempt. Totally > severing pattern syn

Re: Rewrite rules involving LHS lambda?

2017-12-02 Thread Edward Kmett
I don't knw of a formal writeup anywhere. But does that actually mean what you are trying to write? With the effective placement of "forall" quantifiers on the outside for u and v I'd assume that x didn't occur in either u or v. Effectively you have some scope like forall u v. exists x. ... Unde

Re: DeriveFoldable treatment of tuples is surprising

2017-03-21 Thread Edward Kmett
As I recall, Richard Eisenberg has been pushing, off and on, for us to get a better vocabulary to specify "how" something is derived, via DeriveAnyClass, generalized newtype deriving, DeriveFoldable, etc. In general I think the current behavior is the least surprising as it "walks all the a's it c

Re: Derived Functor instance for void types

2017-01-15 Thread Edward Kmett
"Preserving user bottoms" was found to be better behavior for us with Void as well back in the day. Evaluating such a term to get the bottom out is better than making up one that loses information for the user about precisely what bottom it is they had. We do so with absurd and the like for Void.

Re: Retro-Haskell: can we get seq somewhat under control?

2016-12-21 Thread Edward Kmett
Actually, if you go back to the original form of Seq it would translate to data Seq a => Foo a = Foo !Int !a which requires resurrecting DatatypeContexts, and not data Foo a = Seq a => Foo !Int !a The former requires Seq to call the constructor, but doesn't pack the dictionary into the construc

Re: Looking for GHC compile-time performance tests

2016-05-05 Thread Edward Kmett
vector-algorithms has gotten slower to both compile and for users rather consistently during each release throughout the 7.x lifecycle. That may serve as a good torture test as well. > On May 6, 2016, at 6:22 AM, Erik de Castro Lopo wrote: > > Ben Gamari wrote: > >> So, if you would like to s

Re: suppress warning "Defined but not used: type variable ‘x’" in GHC-8.0

2016-01-17 Thread Edward Kmett
Moreover those _'d type variables would infect all of our haddocks. ___ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users

Re: suppress warning "Defined but not used: type variable ‘x’" in GHC-8.0

2016-01-17 Thread Edward Kmett
t; (At least I think I did that somewhere...) > On Jan 16, 2016 9:24 PM, "Edward Kmett" wrote: > >> As a data point I now get thousands of occurrences of this warning across >> my packages. >> >> It is quite annoying. >> >> class Foo a where >&

Re: suppress warning "Defined but not used: type variable ‘x’" in GHC-8.0

2016-01-16 Thread Edward Kmett
As a data point I now get thousands of occurrences of this warning across my packages. It is quite annoying. class Foo a where type Bar a instance Foo [a] where type Bar [a] = Int is enough to trigger it. And you can't turn it off by using _ as instance Foo [_] where type Bar [_] = Int

Re: Arithmetic overflow in rem and mod

2015-06-02 Thread Edward Kmett
We went round and round on this back in August. The ultimate decision was to leave the existing behavior for quot and div as sufficient consensus for changing it was not reached. I've updated the ticket in question to reflect that resolution. -Edward On Mon, Jun 1, 2015 at 6:40 PM, Nikita Karet

Re: -Wall and the fail method

2015-05-22 Thread Edward Kmett
It probably doesn't belong in -Wall, as it is a fairly common idiom to use fail intentionally this way, but it could pretty easily be added to the 'do' and list/monad comprehension desugaring to issue a separate warning that we don't turn on by default. Making it possible to see where you use 'fai

Re: Qualified names in TH?

2015-03-16 Thread Edward Kmett
Using {-# LANGUAGE TemplateHaskell #-} you can use 'foo and ''Foo to get access to the names in scope in the module that is building the splice, rather than worrying about what names are in scope in the module the code gets spliced into. -Edward On Mon, Mar 16, 2015 at 10:54 PM, J. Garrett Morris

Re: GHC 7.10 regression when using foldr

2015-01-20 Thread Edward Kmett
I was assuming that the list was generated by doing more or less the same check we do now. I haven't looked at the code for it. If so, then it seems it wouldn't flag a now-unnecessary Data.Traversable dependency for instance. At least not without rather significant retooling. I might be off in my

Re: GHC 7.10 regression when using foldr

2015-01-20 Thread Edward Kmett
It isn't without a cost. On the down-side, the results of -ddump-minimal-imports would be er.. less minimal. On Tue, Jan 20, 2015 at 6:47 PM, Edward Z. Yang wrote: > I like this proposal: if you're explicit about an import that > would otherwise be implicit by Prelude, you shouldn't get a > wa

Re: "Found hole"

2015-01-20 Thread Edward Kmett
FWIW- you can think of a 'hole' as a "not in scope" error with a ton of useful information about the type such a term would have to have in order to go in the location you referenced it. This promotes a very useful style of type-driven development that is common in Agda, where you write out your p

Re: GHC 7.10 regression when using foldr

2015-01-20 Thread Edward Kmett
Sure. Adding it to the CHANGELOG makes a lot of sense. I first found out about it only a few weeks ago when Herbert mentioned it in passing. Of course, the geek in me definitely prefers technical fixes to human ones. Humans are messy. =) I'd be curious how much of the current suite of warnings c

Re: GHC 7.10 regression when using foldr

2015-01-20 Thread Edward Kmett
Building -Wall clean across this change-over has a big of a trick to it. The easiest way I know of when folks already had lots of import Data.Foldable import Data.Traversable stuff is to just add import Prelude explicitly to the bottom of your import list rather than painstakingly exclude the

Re: GHC 7.10 regression when using foldr

2015-01-20 Thread Edward Kmett
On Tue, Jan 20, 2015 at 9:00 AM, Kim-Ee Yeoh wrote: > > There are few reports because the change hasn't affected the dark majority > yet. RC builds are used by a tiny fraction. There's a long tail of users > still on 7.6, 7.4, 7.2, and 6.x. > We've been actively testing since the first time we

Re: GHC 7.10 regression when using foldr

2015-01-20 Thread Edward Kmett
There is a limited set of situations where the new signatures can fail to infer, where it would infer before. This can happen when you construct a Foldable/Traversable value using polymorphic tools (like Read) that were previously instantiated for list, but where since foldr et al. are now polymor

Re: Equality Constraints (a ~ b)

2015-01-11 Thread Edward Kmett
They were introduced as part of the System Fc rewrite. The Fc approach has the benefit of unifying a lot of the work on GADTs, functional dependencies, type and data families, etc. all behind the scenes. Every once in a while, (~) constraints can leak into the surface language and it can be usefu

Re: Permitting trailing commas for record syntax ADT declarations

2014-09-29 Thread Edward Kmett
Not a concrete suggestion, but just a related data point / nod to the sanity of the suggestion: I'm not sure I'd remove them entirely either, but FWIW, we don't require commas in fixity declarations in Ermine and it works well. On the other hand, our import lists are rather more complicated than

Re: Old code broken by new Typeable class

2014-08-05 Thread Edward Kmett
If you can't change the definition you can use the syntax Björn Bringert added back in 2006 or so for StandaloneDeriving. Just turn on {-# LANGUAGE StandaloneDeriving, DeriveDataTypeable #-} and then you can use deriving instance Typeable Foo -Edward On Tue, Aug 5, 2014 at 1:47 PM, Volker Wy

Re: Overlapping and incoherent instances

2014-07-31 Thread Edward Kmett
Now if only we could somehow find a way to do the same thing for AllowAmbiguousTypes. :) I have a 2500 line file that I'm forced to turn on AllowAmbiguousTypes in for 3 definitions, and checking that I didn't accidentally make something else ambiguous to GHC's eyes is a rather brutal affair. (I ca

Re: Why no `instance (Monoid a, Applicative f)=> Monoid (f a)` for IO?

2014-07-14 Thread Edward Kmett
There are monads for which you want another Monoid, e.g. Maybe provides a different unit, because it pretends to lift a Semigroup into a Monoid. There are also monoids that take a parameter of kind * that would overlap with this instance. So we can't (and shouldn't) have the global Monoid instanc

Re: Monomorphizing GHC Core?

2014-06-19 Thread Edward Kmett
ree k 0 a > > B :: k (Tree k n a) -> Tree k (1+n) a > > This way, after monomorphization, there won't be any sums remaining. > > -- Conal > > > > On Thu, Jun 19, 2014 at 1:22 PM, Edward Kmett wrote: > >> Might you have more success with a Reynolds s

Re: Monomorphizing GHC Core?

2014-06-19 Thread Edward Kmett
Might you have more success with a Reynolds style defunctionalization pass for the polymorphic recursion you can't eliminate? Then you wouldn't have to rule out things like data Complete a = S (Complete (a,a)) | Z a which don't pass that test. -Edward On Thu, Jun 19, 2014 at 3:28 PM, Conal El

Re: [core libraries] Re: Tightening up on inferred type signatures

2014-04-30 Thread Edward Kmett
Er.. my mistake. Control.Applicative. That is what it is we don't re-export that is used in Traversal. =) On Wed, Apr 30, 2014 at 2:47 AM, Edward Kmett wrote: > Not sure. > > An even simpler case is something like exporting a Traversal but not > exporting Data.Traversable,

Re: [core libraries] Re: Tightening up on inferred type signatures

2014-04-29 Thread Edward Kmett
hand without extra imports, just to avoid cluttering the namespace. -Edward On Wed, Apr 30, 2014 at 2:10 AM, Ganesh Sittampalam wrote: > On 23/04/2014 20:04, dm-list-haskell-librar...@scs.stanford.edu wrote: > > Edward Kmett writes: > > > >> You can wind up in perfectl

Re: RFC: changes to -i flag for finding source files

2014-04-25 Thread Edward Kmett
You can actually make symbolic links (as well as hard links and "directory junctions") on windows. -Edward > On Apr 25, 2014, at 12:51 PM, Roman Cheplyaka wrote: > > * Felipe Lessa [2014-04-25 13:01:43-0300] >> Em 25-04-2014 12:22, Edward Kmett escreveu: >&g

Re: RFC: changes to -i flag for finding source files

2014-04-25 Thread Edward Kmett
dward > On Apr 25, 2014, at 12:01 PM, Felipe Lessa wrote: > > Em 25-04-2014 12:22, Edward Kmett escreveu: >> +1 from me. I have a lot of projects that suffer with 4 levels of vacuous >> subdirectories just for this. >> >> In theory cabal could support this on ol

Re: RFC: changes to -i flag for finding source files

2014-04-25 Thread Edward Kmett
+1 from me. I have a lot of projects that suffer with 4 levels of vacuous subdirectories just for this. In theory cabal could support this on older GHC versions by copying all of the files to a working dir in dist with the expected layout on older GHCs. That would enable this to get much greate

Re: [core libraries] Re: Tightening up on inferred type signatures

2014-04-23 Thread Edward Kmett
You can wind up in perfectly legitimate situations where the name for the type you are working with isn't in scope, but where you can write a combinator that would infer to have that type. I'd hate to lose that. It is admittedly of marginal utility at first glance, but there are some tricks that a

Re: [core libraries] Tightening up on inferred type signatures

2014-04-21 Thread Edward Kmett
No objections here. The types involved really *do* have FlexibleContexts in them, so it makes sense to require the extension. The upgrade path for library authors is also clear. It'll complain to add the extension, and they'll fix it by adding the line of code suggested and perhaps realize someth

Re: [Haskell-cafe] Eta Reduction

2014-04-01 Thread Edward Kmett
were to suggest that on a different day, +1 from me. > > John > >> On Apr 1, 2014 10:32 AM, "Edward Kmett" wrote: >> John, >> >> Check the date and consider the process necessary to "enumerate all Haskell >> programs and check their types&q

Re: [Haskell-cafe] Eta Reduction

2014-04-01 Thread Edward Kmett
John, Check the date and consider the process necessary to "enumerate all Haskell programs and check their types". -Edward On Tue, Apr 1, 2014 at 9:17 AM, John Lato wrote: > I think this is a great idea and should become a top priority. I would > probably start by switching to a type-class-ba

Re: PROPOSAL: Literate haskell and module file names

2014-03-17 Thread Edward Kmett
rticularly care what as long as we pick something. > Patching tools to support whatever solution we pick should be trivial. > > Cheers, > Merijn > > On Mar 16, 2014, at 16:41 , Edward Kmett wrote: > > One problem with Foo.*.hs or even Foo.md.hs mapping to the module name Foois

Re: Safe Haskell trust

2014-03-16 Thread Edward Kmett
Not directly. You can, however, make a Trustworthy module that re-exports the (parts of) the Unsafe ones you want to allow yourself to use. -Edward On Sun, Mar 16, 2014 at 12:57 PM, Fabian Bergmark wrote: > Im using the Hint library in a project where users are able to upload > and run code. A

Re: PROPOSAL: Literate haskell and module file names

2014-03-16 Thread Edward Kmett
One problem with Foo.*.hs or even Foo.md.hs mapping to the module name Foois that as I recall JHC will look for Data.Vector in Data.Vector.hs as well as Data/Vector.hs This means that on a case insensitive file system Foo.MD.hs matches both conventions. Do I want to block an change to GHC because

Re: Enabling TypeHoles by default

2014-01-14 Thread Edward Kmett
It actually can affect what code compiles with -fdefer-type-errors, but I don't feel terribly strongly about that. -Edward On Tue, Jan 14, 2014 at 12:23 PM, Joachim Breitner wrote: > Hi, > > heh, I wanted to throw in the same argument: If its just more elaborate > error messages, why do we n

Re: Enabling TypeHoles by default

2014-01-13 Thread Edward Kmett
Heck if we wanted to bikeshed the name, even 'Holes' would do. ;) On Mon, Jan 13, 2014 at 4:30 PM, Daniil Frumin wrote: > On ghc-dev Dominique Devriese has actually proposed changing TypeHoles > to TypedHoles or to something similar, because "TypeHoles" sounds like > you can have holes in types

Re: Enabling TypeHoles by default

2014-01-13 Thread Edward Kmett
I have to admit, I rather like this suggestion. -Edward On Mon, Jan 13, 2014 at 1:42 PM, Krzysztof Gogolewski < krz.gogolew...@gmail.com> wrote: > Hello, > > As discussed on ghc-devs, I propose to enable -XTypeHoles in GHC by > default. Rationale: > > (1) This way holes are far easier to use; j

Re: Why cannot inferred type signatures restrict (potentially) ambiguous type variables?

2013-10-14 Thread Edward Kmett
AllowAmbiguousTypes at this point only extends to signatures that are explicitly written. This would need a new "AllowInferredAmbiguousTypes" or something. On Sat, Oct 12, 2013 at 5:34 PM, adam vogt wrote: > Hello, > > I have code: > > {-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, > S

Re: default roles

2013-10-11 Thread Edward Kmett
handled every attack I've come up with. I'll go back to looking for other attack vectors. -Edward > *From:* Edward Kmett [mailto:ekm...@gmail.com] > *Sent:* 11 October 2013 03:09 > *To:* Richard Eisenberg > *Cc:* David Menendez; glasgow-haskell-users@haskell.org Mailing Li

Re: default roles

2013-10-10 Thread Edward Kmett
Wait, that sounds like it induces bad semantics. Can't we use that as yet another way to attack the sanctity of Set? class Ord a => Foo a where badInsert :: a -> Set a -> Set a instance Foo Int where badInsert = insert newtype Bar = Bar Int deriving (Eq,Foo) instance Ord Bar where compar

Re: default roles

2013-10-09 Thread Edward Kmett
== x) > > > What does `useOrdInstance (MkAge 5)` yield? It yields `False` (in HEAD). > This means that the existing GND mechanism (I didn't change anything around > this part of the code) uses superclass instances for the *newtype*, not for > the *base type*. So, even with super

Re: default roles

2013-10-09 Thread Edward Kmett
On Wed, Oct 9, 2013 at 3:21 PM, Richard Eisenberg wrote: > Now I think we're on the same page, and I *am* a little worried about the > sky falling because of this. (That's not a euphemism -- I'm only a little > worried.) > =) > Wait! I have an idea! > The way I've been describing GND all along

Re: default roles

2013-10-09 Thread Edward Kmett
on on datatypes -- Haskell doesn't really support > "abstract" classes), but perhaps we have to find a way to stop these > incoherent instances from forming. Maybe the use of a constraint makes a > datatype's role be nominal? > > Richard > > On Oct 9, 2013, at 1:55 PM,

Re: default roles

2013-10-09 Thread Edward Kmett
I just noticed there is a pretty big issue with the current default role where typeclasses are concerned! When implementing Data.Type.Coercion I had to use the fact that I could apply coerce to the arguments of data Coercion a b where Coercion :: Coercible a b => Coercion a b This makes sense

Re: Desugaring do-notation to Applicative

2013-10-02 Thread Edward Kmett
That is admittedly a pretty convincing example that we may want to provide either a LANGUAGE pragma or a different syntax to opt in. As a data point in this space, the version of the code I have in scheme calls the version of 'do' that permits applicative desugaring 'ado'. A port of it to Haskell

Re: Liberalising IncoherentInstances

2013-07-29 Thread Edward Kmett
I'll probably never use it, but I can't see any real problems with the proposal. In many ways it is what I always expected IncoherentInstances to be. One thing you might consider is that if you have to make an arbitrary instance selection at the end during compile time, making that emit a warning

Re: How to fix DatatypeContexts?

2013-07-18 Thread Edward Kmett
This is exactly what GADTs are for. -Edward On Thu, Jul 18, 2013 at 6:54 AM, harry wrote: > data Eq a => Pair a = Pair {x::a, y::a} > > equal :: Pair a -> Bool > equal pair = (x pair) == (y pair) > > This code will fail to compile, even with the deprecated DatatypeContexts > extension, because

Re: Field accessor type inference woes

2013-07-02 Thread Edward Kmett
On Tue, Jul 2, 2013 at 4:53 AM, AntC wrote: > > > > I was envisaging that we might well need a functional dependency > > > > Hi Adam, Edward, (Simon), > > I think we should be really careful before introducing FunDeps (or type > functions). > > Can we get to the needed type inference with Undecid

Re: Field accessor type inference woes

2013-07-01 Thread Edward Kmett
mes impossible to write code that is polymorphic and have it get the more general signature without putting dummies in scope just to force conflict. -Edward > Thanks, > > Adam > > > On 01/07/13 15:48, Edward Kmett wrote: > > It strikes me that there is a fairly

Field accessor type inference woes

2013-07-01 Thread Edward Kmett
It strikes me that there is a fairly major issue with the record proposal as it stands. Right now the class class Has (r :: *) (x :: Symbol) (t :: *) can be viewed as morally equivalent to having several classes class Foo a b where foo :: a -> b class Bar a b where bar

Re: A possible alternative to dot notation for record access

2013-06-30 Thread Edward Kmett
AM, Edward Kmett wrote: > (#) is a legal operator today and is used in a number of libraries. > > > On Sun, Jun 30, 2013 at 11:38 PM, wrote: > >> As long as we're bikeshedding... >> >> Possibly '#' is unused syntax -- Erlang uses it for its records t

Re: A possible alternative to dot notation for record access

2013-06-30 Thread Edward Kmett
(#) is a legal operator today and is used in a number of libraries. On Sun, Jun 30, 2013 at 11:38 PM, wrote: > As long as we're bikeshedding... > > Possibly '#' is unused syntax -- Erlang uses it for its records too, so we > wouldn't be pulling it out of thin air. E.g. "person#firstName" > > Tom

Re: Overloaded record fields

2013-06-27 Thread Edward Kmett
On Thu, Jun 27, 2013 at 2:14 AM, AntC wrote: > > Edward Kmett gmail.com> writes: > > > > Let me take a couple of minutes to summarize how the lens approach > tackles the composition problem today without requiring confusing changes > in the lexical structure of

Re: Overloaded record fields

2013-06-26 Thread Edward Kmett
Let me take a couple of minutes to summarize how the lens approach tackles the composition problem today without requiring confusing changes in the lexical structure of the language. I'll digress a few times to showcase how this actually lets us make more powerful tools than are available in stand

Re: Overloaded record fields

2013-06-26 Thread Edward Kmett
Note: the lens solution already gives you 'reverse function application' with the existing (.) due to CPS in the lens type. -Edward On Wed, Jun 26, 2013 at 4:39 PM, Simon Peyton-Jones wrote: > | record projections. I would prefer to have dot notation for a > | general, very tightly-binding re

Re: base package (Was: GHC 7.8 release?)

2013-02-21 Thread Edward Kmett
Comparing hash, ptr, str gives you a pretty good acceptance/rejection test. hash for the quick rejection, ptr for quick acceptance, str for accuracy. Especially since the particular fingerprints for Typeable at least are usually made up of 3 bytestrings that were just stuffed in and forgotten about

Re: data kinds

2013-01-27 Thread Edward Kmett
This has the problem that kind is currently a valid function name, so it would take a new keyword, or at least on conditional on the DataKinds extension. -Edward On Sun, Jan 27, 2013 at 3:02 AM, Erik Hesselink wrote: > When we discussed this last time (summarized by the link Pedro sent, I >> th

Re: Newtype wrappers

2013-01-14 Thread Edward Kmett
No magic coercing is present in the proposal. You need to use explicit newtype wrap and newtype unwrap expressions. Sent from my iPad On Jan 14, 2013, at 6:42 PM, Johan Tibell wrote: > On Mon, Jan 14, 2013 at 3:40 PM, Evan Laforge wrote: >> Wait, what's the runtime error? Do you mean messing

Re: Newtype wrappers

2013-01-14 Thread Edward Kmett
;> ** ** >> >> I don’t want to involve type classes, nor Functor. We don’t even have a >> good way to say “is a functor of its second type argument” for a type >> constructor of three arguments. >> >> ** ** >> >> Simon >> >>

Re: Newtype wrappers

2013-01-14 Thread Edward Kmett
> good way to say “is a functor of its second type argument” for a type > constructor of three arguments. > > ** ** > > Simon**** > > ** ** > > ** ** > > ** ** > > *From:* Edward Kmett [mailto:ekm...@gmail.com] > *Sent:* 14 January 2013 18:3

Re: Newtype wrappers

2013-01-14 Thread Edward Kmett
Many of us definitely care. =) The main concern that I would have is that the existing solutions to this problem could be implemented while retaining SafeHaskell, and I don't see how a library that uses this can ever recover its SafeHaskell guarantee. Here is a straw man example of a solution tha

Re: Generating random type-level naturals

2012-11-16 Thread Edward Kmett
x27;ll cut to the chase. The basic idea is that we just need to be >> able to hide our dependent types from the compiler. That is, we can't >> define: >> >> reifyInt :: (n::Int) -> ...n... >> >> but only because we're not allo

Re: TypeHoles: unbound variables as named holes

2012-10-05 Thread Edward Kmett
On Fri, Oct 5, 2012 at 10:22 AM, Sean Leather wrote: > I also like the proposal; however, I think it only makes sense if the set > of unbound variables with the same name is treated as referring to the same > identifier. This was, after all, the main reason for named holes. Roman > expected this,

Re: Comments on current TypeHoles implementation

2012-10-04 Thread Edward Kmett
I really like this proposal. -Edward On Thu, Oct 4, 2012 at 5:40 AM, Simon Peyton-Jones wrote: > There is also the small matter, in this example, of distinguishing which > `_' is which. The description works, but you have to think about it. I > don't have an immediate and simple solution to thi

Re: Comments on current TypeHoles implementation

2012-10-03 Thread Edward Kmett
On Wed, Oct 3, 2012 at 11:44 AM, Sean Leather wrote: > Hi Simon, > > Thanks for all your work in getting TypeHoles into HEAD. We really > appreciate it. > > I was playing around with HEAD today and wanted to share a few > observations. > > (1) One of the ideas we had was that a hole `_' would be

Re: Why is Bag's Data instance "broken"?

2012-09-20 Thread Edward Kmett
Data (see http://hackage.haskell.org/trac/ghc/ticket/7256). I think > those are just > a bug, unrelated to the abstraction story, no? > > > Cheers, > Pedro > > > On Thu, Sep 20, 2012 at 12:19 PM, Edward Kmett wrote: > >> Note: It was probably built with an eye t

Re: Why is Bag's Data instance "broken"?

2012-09-20 Thread Edward Kmett
Note: It was probably built with an eye towards how Data.Map and the like performed abstraction. However, This isn't necessary to protect the invariants of a bag. The constructors exposed via Data do not have to be the actual constructors of the data type. With this you can quotient out the portio

Re: Type operators in GHC

2012-09-17 Thread Edward Kmett
On Mon, Sep 17, 2012 at 1:02 PM, Sjoerd Visscher wrote: > Hi, > > Note that nobody was suggesting two pragmas with incompatible behaviors, > only to have just one symbol reserved to still be able to have type > operator variables. > An issue with reserving a symbol for type operator variables is

Re: Type operators in GHC

2012-09-17 Thread Edward Kmett
Iavor: Wow, I really like the >--c--> trick at the type level. Note: we can shorten that somewhat and improve the fixity to associate correctly, matching the associativity of (->), which fortunately associates to the right. (associating to the left can be done with a similar trick, based on the or

Re: Type operators in GHC

2012-09-15 Thread Edward Kmett
One issue with this proposal is it makes it *completely* impossible to pick a type constructor operator that works with both older GHCs and 7.6. It is a fairly elegant choice, but in practice it would force me and many others to stop using them completely for the next couple of years, as I wouldn'

Re: PolyKind issue in GHC 7.6.1rc1: How to make a kind a functional dependency?

2012-09-05 Thread Edward Kmett
I've come to think the culprit here is the fallacy that Any should inhabit every kind. I realize this is useful from an implementation perspective, but it has a number of far reaching consequences: This means that a product kind isn't truly a product of two kinds. x * y, it winds up as a *disting

Re: PolyKind issue in GHC 7.6.1rc1: How to make a kind a functional dependency?

2012-08-31 Thread Edward Kmett
explain what you want in System FC? Type inference and the > surface language come after that. If it can’t be expressed in FC it’s out > of court. Of course we can always beef up System FC. > > ** ** > > I’m copying Stephanie and Conor who may have light to shed.***

Re: PolyKind issue in GHC 7.6.1rc1: How to make a kind a functional dependency?

2012-08-31 Thread Edward Kmett
aZ8} k{tv l} [sig] ghc-prim:GHC.Prim.BOX{(w) tc 347} I'll try to distill this down to a reasonable test case. -Edward On Fri, Aug 31, 2012 at 1:26 PM, Edward Kmett wrote: > It is both perfectly reasonable and unfortunately useless. :( > > The problem is that the "mor

Re: PolyKind issue in GHC 7.6.1rc1: How to make a kind a functional dependency?

2012-08-31 Thread Edward Kmett
, GADTs #-} > > module Product where > > ** ** > > data Star :: (x -> x -> *) -> (y -> y -> *) -> (x,y) -> (x,y) -> * where** > ** > > (:*) :: x a b -> y c d -> Star x y '(a,c) '(b,d) > > ** ** > > bidStar :: S

Re: PolyKind issue in GHC 7.6.1rc1: How to make a kind a functional dependency?

2012-08-31 Thread Edward Kmett
On Fri, Aug 31, 2012 at 9:37 AM, Richard Eisenberg wrote: > I ran into this same issue in my own experimentation: if a type variable x > has a kind with only one constructor K, GHC does not supply the equality x > ~ K y for some fresh type variable y. Perhaps it should. I too had to use > similar

Re: PolyKind issue in GHC 7.6.1rc1: How to make a kind a functional dependency?

2012-08-31 Thread Edward Kmett
do eta expansion. I wonder if this could be made less painful. On Fri, Aug 31, 2012 at 8:55 AM, Edward Kmett wrote: > Hrmm. This seems to work manually for getting product categories to work. > Perhaps I can do the same thing for thrists. > > {-# LANGUAGE PolyKinds, DataKinds, TypeOpe

Re: PolyKind issue in GHC 7.6.1rc1: How to make a kind a functional dependency?

2012-08-31 Thread Edward Kmett
y (Snd a) (Snd b) -> (x * y) a b instance (Category x, Category y) => Category (x * y) where id = id :* id (xf :* yf) . (xg :* yg) = (xf . xg) :* (yf . yg) On Fri, Aug 31, 2012 at 8:44 AM, Edward Kmett wrote: > Hrmm. This seems to render product kinds rather useless, as there is no &g

Re: PolyKind issue in GHC 7.6.1rc1: How to make a kind a functional dependency?

2012-08-31 Thread Edward Kmett
re > > ** ** > > class IMonad (m :: (k -> *) -> k -> *) | m -> k where > > ireturn :: a x -> m a x > > ** ** > > infixr 5 :- > > ** ** > > data Thrist :: ((i,i) -> *) -> (i,i) -> * where > > Nil :: Thrist a &#x

Re: PolyKind issue in GHC 7.6.1rc1: How to make a kind a functional dependency?

2012-08-31 Thread Edward Kmett
olving kinds are > supported. Are you compiling with a version of 7.6 updated since that bug > fix? > > Richard > > On Aug 30, 2012, at 10:38 PM, Edward Kmett wrote: > > If I define the following > > {-# LANGUAGE FunctionalDependencies, GADTs, KindSignatures, > Multi

PolyKind issue in GHC 7.6.1rc1: How to make a kind a functional dependency?

2012-08-30 Thread Edward Kmett
If I define the following {-# LANGUAGE FunctionalDependencies, GADTs, KindSignatures, MultiParamTypeClasses, PolyKinds, RankNTypes, TypeOperators, DefaultSignatures, DataKinds, FlexibleInstances, UndecidableInstances #-} module Indexed.Test where class IMonad (m :: (k -> *) -> k -> *) where ire

Re: Why is Bag's Data instance "broken"?

2012-08-29 Thread Edward Kmett
I've been meaning to put in a proposal to replace the Data instances for Map, etc. with one that pretends there is a fake 'fromList' constructor that restores the invariants. In my experience this works much better than just making everyone who relies on Data randomly crash, and it preserves the i

Re: Comparing StableNames of different type

2012-08-28 Thread Edward Kmett
On Tue, Aug 28, 2012 at 12:08 PM, Nicolas Frisby wrote: > On Tue, Aug 28, 2012 at 3:34 AM, Simon Marlow wrote: > On 24/08/2012 07:39, Emil Axelsson wrote: > > > > Are there any dangers in comparing two StableNames of different type? > > > >stEq :: StableName a -> StableNa

Re: Comparing StableNames of different type

2012-08-24 Thread Edward Kmett
You can wind up with StableNames matching even when the types differ. Consider naming [] :: [Int] and [] :: [()]. This is harmless for most usecases. I've used unsafeCoerce to compare StableNames on different types for years without problems. Admittedly, I do find it a bit of an oddity that the

Re: Request for comments on proposal for literate programming using markdown

2012-08-21 Thread Edward Kmett
Ultimately your best bet to actually get something integrated will be to find something that minimizes the amount of work on the part of GHC HQ. I don't think *anybody* there is interested in picking up a lot of fiddly formatting logic and carving it into stone. They might be slightly less inclin

Re: GADTs in the wild

2012-08-14 Thread Edward Kmett
On Tue, Aug 14, 2012 at 10:32 AM, Edward Kmett wrote: > data NonDetFork :: (*,*) -> * -> * where > NDL :: (a -> c) -> NonDetFork '(a, b) c > NDR :: (b -> c) -> NonDetFork '(a, b) c > NDB :: (a -> b) -> (b -> c) -> NonDetFork '(a,

Re: GADTs in the wild

2012-08-14 Thread Edward Kmett
mplemented using a more traditional GADT without poly/data kinds, by just using (a,b) instead of '(a,b), though. -Edward Kmett On Tue, Aug 14, 2012 at 7:32 AM, Simon Peyton-Jones wrote: > Friends > > > I’m giving a series of five lectures at the Laser Summer > School<http:

Re: PolyKinds, Control.Category and GHC 7.6.1

2012-08-13 Thread Edward Kmett
changes need be applied beyond permitting the type of Category to generalize and existing code continues to work. This change actually could have been applied in 7.4.1. -Edward Kmett ___ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

PolyKinds, Control.Category and GHC 7.6.1

2012-08-13 Thread Edward Kmett
n base that directly benefits from PolyKinds without any code changes, but without enabling the extension there nobody can define categories for kinds other than *, and most interesting categories actually have more exotic kinds. I only noticed that it wasn't there in the release candidate ju

Re: Call to arms: lambda-case is stuck and needs your help

2012-07-06 Thread Edward Kmett
x27; mx my = case (# mx, my #) of (# Just x, Just y #) -> Just (x + y) (# _ , _ #) -> Nothing bar''' (Just x) (Just y) = Just (x + y) bar''' _ _ = Nothing -Edward On Fri, Jul 6, 2012 at 3:12 AM, Edward Kmett wrote: > Oh, neat. I guess it d

Re: Call to arms: lambda-case is stuck and needs your help

2012-07-06 Thread Edward Kmett
fact that it introduces a layout rule doesn't change any of the rules for when layout is introduced. On Jul 5, 2012, at 5:33 PM, Twan van Laarhoven wrote: > On 2012-07-05 23:04, Edward Kmett wrote: >> A similar generalization can be applied to the expression between case an

Re: Call to arms: lambda-case is stuck and needs your help

2012-07-05 Thread Edward Kmett
I really like the \of proposal! It is a clean elision with \x -> case x of becoming \of I still don't like it directly for multiple arguments. One possible approach to multiple arguments is what we use for multi-argument case/alt here in our little haskell-like language, Ermine, here at S&P Ca

Re: Kindness of strangers (or strangeness of Kinds)

2012-06-11 Thread Edward Kmett
On Mon, Jun 11, 2012 at 9:58 PM, AntC wrote: > Simon Peyton-Jones microsoft.com> writes: > > > > > There is a little, ill-documented, sub-kind hierarchy in GHC. I'm trying > hard to get rid of it as much as > > possible, and it is much less important than it used to be. It's always > been > the

Re: Kindness of strangers (or strangeness of Kinds)

2012-06-08 Thread Edward Kmett
ghci> :k Maybe Maybe :: * -> * On Sat, Jun 9, 2012 at 1:34 AM, Rustom Mody wrote: > On Thu, Jun 7, 2012 at 7:16 AM, AntC wrote: > >> I'm confused about something with promoted Kinds (using an example with >> Kind- >> promoted Nats). >> >> This is in GHC 7.4.1. (Apologies if this is a known bug/

  1   2   >