Re: Enabling TypeHoles by default

2014-01-13 Thread Krzysztof Gogolewski
> Will any freevariable be considered a type hole? Or just _blah and _ ?
-XTypeHoles makes holes only out of _blah (where _blah is not in scope) and
_.


On Mon, Jan 13, 2014 at 8:11 PM, Carter Schonwald <
carter.schonw...@gmail.com> wrote:

> +1. Will any freevariable be considered a type hole? Or just _blah and _ ?
>
>
> On Mon, Jan 13, 2014 at 2:07 PM, Erik Hesselink wrote:
>
>> I think that's a good idea. It was also suggested in a reddit thread
>> [0] a year ago, and it doesn't seem like that thread has any arguments
>> against it.
>>
>> Erik
>>
>> [0]
>> http://www.reddit.com/r/haskell/comments/10u7xr/ghc_head_now_features_agdalike_holes/c6gvy0r
>>
>> On Mon, Jan 13, 2014 at 8:03 PM, migmit  wrote:
>> > Agreed. Having it in 7.8 would be very nice, and yes, I don't see how
>> it can
>> > break anything.
>> >
>> > Отправлено с iPad
>> >
>> > 13 янв. 2014 г., в 22:54, Edward Kmett  написал(а):
>> >
>> > I have to admit, I rather like this suggestion.
>> >
>> > -Edward
>> >
>> >
>> > On Mon, Jan 13, 2014 at 1:42 PM, Krzysztof Gogolewski
>> >  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; just entering "_" allows to
>> >> check type of a subexpression, no need of adding "-XTypeHoles".
>> >>
>> >> (2) This affects error messages only; i.e. the set of programs that
>> >> compile stays the same - Haskell 2010. The only exception is that if
>> you use
>> >> -fdefer-type-errors, then a program with a hole compiles, but this
>> seems
>> >> fine with philosophy of -fdefer-type-errors.
>> >>
>> >> If so: would you like it to be in 7.8 or wait a cycle? My preference is
>> >> 7.8, two people (John and Richard) suggested 7.10.
>> >>
>> >> -KG
>> >>
>> >> ___
>> >> 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
>> >
>> ___
>> 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


Enabling TypeHoles by default

2014-01-13 Thread Krzysztof Gogolewski
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; just entering "_" allows to check
type of a subexpression, no need of adding "-XTypeHoles".

(2) This affects error messages only; i.e. the set of programs that compile
stays the same - Haskell 2010. The only exception is that if you use
-fdefer-type-errors, then a program with a hole compiles, but this seems
fine with philosophy of -fdefer-type-errors.

If so: would you like it to be in 7.8 or wait a cycle? My preference is
7.8, two people (John and Richard) suggested 7.10.

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


Re: TypeHoles behaviour

2013-08-27 Thread Krzysztof Gogolewski
I have also seen this behaviour and support the change.
-KG

2013/8/27 Austin Seipp 

> I'm +1 on changing the behavior. I find it probably the most confusing
> aspect of using TypeHoles, which is otherwise great.
>
> On Tue, Aug 27, 2013 at 3:17 AM, Simon Peyton-Jones
>  wrote:
> > I'm sympathetic to Andres's point here. Easy to implement. Any
> objections?
> >
> > Simon
> >
> > | -Original Message-
> > | From: Glasgow-haskell-users [mailto:glasgow-haskell-users-
> > | boun...@haskell.org] On Behalf Of Andres Löh
> > | Sent: 23 August 2013 21:02
> > | To: glasgow-haskell-users@haskell.org
> > | Subject: TypeHoles behaviour
> > |
> > | Hi.
> > |
> > | I've just started playing with TypeHoles. (I'm writing some Haskell
> > | course
> > | materials and would like to use them from the very beginning once they
> > | become
> > | available.)
> > |
> > | However, I must say that I don't understand the current notion of
> > | "relevance"
> > | that seems to determine whether local bindings are included or not.
> > |
> > | The current rule seems to be that bindings are included only if the
> > | intersection between the type variables their types involve and the
> type
> > | variables in the whole is non-empty. However, I think this is
> confusing.
> > |
> > | Let's look at a number of examples:
> > |
> > | > f1 :: Int -> Int -> Int
> > | > f1 x y = _
> > |
> > | Found hole '_' with type: Int
> > | In the expression: _
> > | In an equation for 'f1': f1 x y = _
> > |
> > | No bindings are shown.
> > |
> > | > f2 :: a -> a -> a
> > | > f2 x y = _
> > |
> > | Found hole '_' with type: a
> > | Where: 'a' is a rigid type variable bound by
> > |the type signature for f2 :: a -> a -> a at List.hs:6:7
> > | Relevant bindings include
> > |   f2 :: a -> a -> a (bound at List.hs:7:1)
> > |   x :: a (bound at List.hs:7:4)
> > |   y :: a (bound at List.hs:7:6)
> > | In the expression: _
> > | In an equation for 'f2': f2 x y = _
> > |
> > | Both x and y (and f2) are shown. Why should this be treated differently
> > | from f1?
> > |
> > | > f3 :: Int -> (Int -> a) -> a
> > | > f3 x y = _
> > |
> > | Found hole '_' with type: a
> > | Where: 'a' is a rigid type variable bound by
> > |the type signature for f3 :: Int -> (Int -> a) -> a at
> > | List.hs:9:7
> > | Relevant bindings include
> > |   f3 :: Int -> (Int -> a) -> a (bound at List.hs:10:1)
> > |   y :: Int -> a (bound at List.hs:10:6)
> > | In the expression: _
> > | In an equation for 'f3': f3 x y = _
> > |
> > | Here, y is shown, but x isn't, even though y has to be applied to an
> Int
> > | in order to produce an a. Of course, it's possible to obtain an Int
> from
> > | elsewhere ...
> > |
> > | f4 :: a -> (a -> b) -> b
> > | f4 x y = _
> > |
> > | Found hole '_' with type: b
> > | Where: 'b' is a rigid type variable bound by
> > |the type signature for f4 :: a -> (a -> b) -> b at
> > | List.hs:12:7
> > | Relevant bindings include
> > |   f4 :: a -> (a -> b) -> b (bound at List.hs:13:1)
> > |   y :: a -> b (bound at List.hs:13:6)
> > | In the expression: _
> > | In an equation for 'f4': f4 x y = _
> > |
> > | Again, only y is shown, and x isn't. But here, the only sane way of
> > | filling
> > | the hole is by applying "y" to "x". Why is one more relevant than the
> > | other?
> > |
> > | f5 x y = _
> > |
> > | Found hole '_' with type: t2
> > | Where: 't2' is a rigid type variable bound by
> > | the inferred type of f5 :: t -> t1 -> t2 at
> List.hs:15:1
> > | Relevant bindings include
> > |   f5 :: t -> t1 -> t2 (bound at List.hs:15:1)
> > | In the expression: _
> > | In an equation for 'f5': f5 x y = _
> > |
> > | Neither x and y are included without a type signature. Even though all
> > | of
> > | the above types are admissible, which would convince GHC that one or
> > | even
> > | all may be relevant.
> > |
> > | IMHO, this isn't worth it. It's a confusing rule. Just include all
> local
> > | bindings
> > | in the output, always. That's potentially verbose, but easy to
> > | understand. It's
> > | also potentially really helpful, because it trains beginning
> programmers
> > | to see
> > | what types local variables get, and it's a way to obtain complex types
> > | of locally
> > | bound variables for expert programmers. It's also much easier to
> > | explain. It
> > | should be easier to implement, too :)
> > |
> > | Could we please change it?
> > |
> > | Cheers,
> > |   Andres
> > |
> > | --
> > | Andres Löh, Haskell Consultant
> > | Well-Typed LLP, http://www.well-typed.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
> >

Re: implicit params in instance contexts

2013-07-16 Thread Krzysztof Gogolewski
GHC ticket:
http://ghc.haskell.org/trac/ghc/ticket/7624


2013/7/16 Ganesh Sittampalam 

> Hi,
>
> It seems that from GHC 7.4, the prohibition on implicit parameter
> constraints in instance declarations has been relaxed. The program below
> gives the error "Illegal constraint ?fooRev::Bool" in GHC 7.2.1 but
> loads fine in GHC 7.4.2 and GHC 7.6.2.
>
> I can't spot anything about this in the release notes, and the
> documentation
> (
> http://www.haskell.org/ghc/docs/7.6.3/html/users_guide/other-type-extensions.html#idp49069584
> )
> still says "You can't have an implicit parameter in the context of a
> class or instance declaration."
>
> So I wonder if this happened by accident, perhaps as part of the
> ConstraintKinds work or similar?
>
> I've wanted this feature a few times so if it's going to stay I might
> start using it. However it is a bit dangerous, so if it was added by
> accident it might warrant some discussion before deciding to keep it.
> For example as the value "set2" below shows, it can be used to violate
> datatype invariants.
>
> Cheers,
>
> Ganesh
>
>
> {-# LANGUAGE ImplicitParams #-}
> module Ord where
>
> import Data.Set ( Set )
> import qualified Data.Set as Set
>
> newtype Foo = Foo Int
> deriving (Eq, Show)
>
> instance (?fooRev :: Bool) => Ord Foo where
> Foo a `compare` Foo b =
> if ?fooRev then b `compare` a else a `compare` b
>
> set1 = let ?fooRev = False in Set.fromList [Foo 1, Foo 3]
>
> set2 = let ?fooRev = True in Set.insert (Foo 2) set1
> -- Ord> set2
> -- fromList [Foo 2,Foo 1,Foo 3]
>
> ___
> 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