Re: New type of ($) operator in GHC 8.0 is problematic

2016-02-04 Thread Roman Cheplyaka
On 02/05/2016 01:31 AM, Edward Z. Yang wrote: > I'm not really sure how you would change the type of 'id' based on > a language pragma. > > How do people feel about a cosmetic fix, where we introduce a new > pragma, {-# LANGUAGE ShowLevity #-} which controls the display of levity > arguments/TYPE.

Re: New type of ($) operator in GHC 8.0 is problematic

2016-02-04 Thread Edward Kmett
Note: (->) is a type. ($) is a term. There is still magic in the typechecker around allowing fully saturated applications of (x -> y) allowing x and y to be in either # or *. My understanding is that (->) isn't really truly levity-polymorphic, but rather acts differently based on the levity of the

Re: New type of ($) operator in GHC 8.0 is problematic

2016-02-04 Thread Iavor Diatchki
Hello, how about we simply use two operators: 1. ($) which only works for standard types (i.e., not #), which we can use 99% of the time, and 2. some other operator which has the levity polymorphic type and would be used in the advanced cases when you are working with unboxed values, etc. Pers

Re: New type of ($) operator in GHC 8.0 is problematic

2016-02-04 Thread Christopher Allen
The sort of pragma you suggest would satisfy me. Pragmas like this don't bother me and make my job a fair bit easier. Too many, "don't worry about this; later" is exhausting. Too many, "don't worry about this; we're not even going to have time to cover it" is demoralizing. On Thu, Feb 4, 2016 at 5

Re: New type of ($) operator in GHC 8.0 is problematic

2016-02-04 Thread Edward Z. Yang
I'm not really sure how you would change the type of 'id' based on a language pragma. How do people feel about a cosmetic fix, where we introduce a new pragma, {-# LANGUAGE ShowLevity #-} which controls the display of levity arguments/TYPE. It's off by default but gets turned on by some extension

Re: New type of ($) operator in GHC 8.0 is problematic

2016-02-04 Thread Christopher Allen
This seems worse than FTP IMO. It's considerably noisier, considerably rarer a concern for Haskell programmers, and is wa beyond the scope of most learning resources. Is there a reason this isn't behind a pragma? On Thu, Feb 4, 2016 at 5:02 PM, Manuel M T Chakravarty wrote: > To be honest,

Re: New type of ($) operator in GHC 8.0 is problematic

2016-02-04 Thread Manuel M T Chakravarty
To be honest, I think, it is quite problematic if an obscure and untested language extension (sorry, but that’s what it is right now) bleeds through into supposedly simple standard functionality. The beauty of most of GHC’s language extensions is that you can ignore them until you need them. Ha

Re: New type of ($) operator in GHC 8.0 is problematic

2016-02-04 Thread Ryan Scott
Out of curiosity, what should the kind of (->) be? Both the argument and result kind of (->) can be either * or #, but we can't make the argument kind levity polymorphic due to [1], right? How would you encode that in a kind signature? Ryan S. - [1] https://ghc.haskell.org/trac/ghc/ticket/1147

Re: New type of ($) operator in GHC 8.0 is problematic

2016-02-04 Thread Christopher Allen
> make the kind of (->) more flexible. Can that wait until 8.2 so we don't have to edit the book as much in preparation for 8.0? :P On Thu, Feb 4, 2016 at 3:15 PM, Richard Eisenberg wrote: > I agree with everything that's been said in this thread, including the > unstated "that type for ($) is

Re: New type of ($) operator in GHC 8.0 is problematic

2016-02-04 Thread Richard Eisenberg
I agree with everything that's been said in this thread, including the unstated "that type for ($) is sure ugly". Currently, saturated (a -> b) is like a language construct, and it has its own typing rule, independent of the type of the type constructor (->). But reading the comment that Ben li

Re: New type of ($) operator in GHC 8.0 is problematic

2016-02-04 Thread Ryan Scott
> My understanding was that the implicitly polymorphic levity, did (->) not > change because it's a type constructor? The kind of (->) as GHCi reports it is technically correct. As a kind constructor, (->) has precisely the kind * -> * -> *. What's special about (->) is that when you have a satur

Re: New type of ($) operator in GHC 8.0 is problematic

2016-02-04 Thread Ben Gamari
Christopher Allen writes: > My understanding was that the implicitly polymorphic levity, did (->) not > change because it's a type constructor? > > Prelude> :info (->) > data (->) a b -- Defined in ‘GHC.Prim’ > Prelude> :k (->) > (->) :: * -> * -> * > > Basically I'm asking why ($) changed and (-

Re: New type of ($) operator in GHC 8.0 is problematic

2016-02-04 Thread Christopher Allen
My understanding was that the implicitly polymorphic levity, did (->) not change because it's a type constructor? Prelude> :info (->) data (->) a b -- Defined in ‘GHC.Prim’ Prelude> :k (->) (->) :: * -> * -> * Basically I'm asking why ($) changed and (->) did not when (->) had similar properties

Re: Guarantees for ST and IO shared in common?

2016-02-04 Thread Christopher Allen
Perfect, thank you very much Simon! I know you're busy so you taking the time to answer questions like this is a much appreciated gift. On Thu, Feb 4, 2016 at 6:11 AM, Simon Peyton Jones wrote: > that the mechanism for preventing things like reordering operations or > spurious sharing is shared

Re: New type of ($) operator in GHC 8.0 is problematic

2016-02-04 Thread Ryan Scott
Hi Chris, The change to ($)'s type is indeed intentional. The short answer is that ($)'s type prior to GHC 8.0 was lying a little bit. If you defined something like this: unwrapInt :: Int -> Int# unwrapInt (I# i) = i You could write an expression like (unwrapInt $ 42), and it would typec

New type of ($) operator in GHC 8.0 is problematic

2016-02-04 Thread Christopher Allen
$ ghci :lGHCi, version 8.0.0.20160122: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/callen/.ghci Prelude> :t ($) ($) :: forall (w :: GHC.Types.Levity) a (b :: TYPE w). (a -> b) -> a -> b As someone that's working on a book for beginners/intermediates and t

Re: Automatically deriving Generic for every algebraic data type

2016-02-04 Thread Andres Löh
I agree with Ryan on this, i.e., a general automatic DeriveGeneric would not be a good idea right now. Note also that it is already the case that if you want to derive certain classes, you may have to derive other classes as well, namely if superclasses are involved. So you cannot say "deriving Ord

Re: Automatically deriving Generic for every algebraic data type

2016-02-04 Thread Roman Cheplyaka
On 02/04/2016 02:19 PM, Wolfgang Jeltsch wrote: > Hi, > > if you do generic programming these days, you can use DeriveAnyClass to > write code like the following (where Serializable is a class with a > generic default implementation): > >> data Tree a = Leaf | Branch (Tree a) a (Tree a) >>

Re: Automatically deriving Generic for every algebraic data type

2016-02-04 Thread Ryan Scott
I'm a pretty solid -1 on this idea. On a general level, I'm opposed to the idea of deriving typeclasses without the programmer opting in. Most typeclasses express operations that your datatype must support, and in the case of Generic(1), it mandates that users can convert between values of your da

Re: Automatically deriving Generic for every algebraic data type

2016-02-04 Thread Oleg Grenrus
Hi, sometimes I want to use Generic derivation, but don’t want expose the Generic instance outside the module. The reason, is that for some types I want to export only smart constructors / modifier lenses; yet the structure is probably simple enough to benefit from `Generic`. If it will be possi

Re: Automatically deriving Generic for every algebraic data type

2016-02-04 Thread Wolfgang Jeltsch
Am Donnerstag, den 04.02.2016, 14:19 +0200 schrieb Wolfgang Jeltsch: > Hi, > > if you do generic programming these days, you can use DeriveAnyClass to > write code like the following (where Serializable is a class with a > generic default implementation): > > > data Tree a = Leaf | Branch (Tree

Automatically deriving Generic for every algebraic data type

2016-02-04 Thread Wolfgang Jeltsch
Hi, if you do generic programming these days, you can use DeriveAnyClass to write code like the following (where Serializable is a class with a generic default implementation): > data Tree a = Leaf | Branch (Tree a) a (Tree a) > deriving (Generic, Serializable) It would be great, i

RE: Guarantees for ST and IO shared in common?

2016-02-04 Thread Simon Peyton Jones
that the mechanism for preventing things like reordering operations or spurious sharing is shared in common between ST and IO via State# Yes. It’s pure data dependency, no more and no less. Operations in both ST and IO take a State# token as input, and produce one as output. So of course to ge