Re: Type operators in GHC

2012-09-14 Thread Cale Gibbard
There's a fair amount of code out there which uses (~>) as a type
variable (we have ~10k lines of heavy arrow code at iPwn). It would be
*really* nice if that could be accommodated somehow. But the proposal
you just gave at least would allow for a textual substitution, so not
quite so bad as having to change everything to prefix notation.

On 14 September 2012 19:26, Simon Peyton-Jones  wrote:
> Fair point.  So you are saying it’d be ok to say
>
>
>
>   data T (.->)  = MkT (Int .-> Int)
>
>
>
> where (.+) is a type variable?   Leaving ordinary (+) available for type
> constructors.
>
>
>
> If we are inverting the convention I wonder whether we might invert it
> completely and use “:” as the “I’m different” herald as we do for
> *constructor* operators in terms.  Thus
>
>
>
>   data T (:->)  = MkT (Int :-> Int)
>
>
>
> That seems symmetrical, and perhaps nicer than having a new notation.
>
>
>
>  In terms  In types
>
> ---
>
> aTerm variable Type variable
>
> AData constructor Type constructor
>
> +Term variable operator   Type constructor operator
>
> :+  Data constructor operator   Type variable operator
>
>
>
> Any other opinions?
>
>
>
> Simon
>
>
>
> From: conal.elli...@gmail.com [mailto:conal.elli...@gmail.com] On Behalf Of
> Conal Elliott
> Sent: 06 September 2012 23:59
> To: Simon Peyton-Jones
> Cc: GHC users
> Subject: Re: Type operators in GHC
>
>
>
> Oh dear. I'm very sorry to have missed this discussion back in January. I'd
> be awfully sad to lose pretty infix notation for type variables of kind * ->
> * -> *. I use them extensively in my libraries and projects, and pretty
> notation matters.
>
> I'd be okay switching to some convention other than lack of leading ':' for
> signaling that a symbol is a type variable rather than constructor, e.g.,
> the *presence* of a leading character such as '.'.
>
> Given the increasing use of arrow-ish techniques and of type-level
> programming, I would not classify the up-to-7.4 behavior as a "foolish
> consistency", especially going forward.
>
> -- Conal
>
> On Wed, Jan 18, 2012 at 6:27 AM, Simon Peyton-Jones 
> wrote:
>
> Dear GHC users
>
> As part of beefing up the kind system, we plan to implement the "Type
> operators" proposal for Haskell Prime
> http://hackage.haskell.org/trac/haskell-prime/wiki/InfixTypeConstructors
>
> GHC has had type operators for some kind, so you can say
> data a :+: b = Left a | Right b
> but you can only do that for operators which start with ":".
>
> As part of the above wiki page you can see the proposal to broaden this to
> ALL operators, allowing
> data a + b = Left a | Right b
>
> Although this technically inconsistent the value page (as the wiki page
> discussed), I think the payoff is huge. (And "A foolish consistency is the
> hobgoblin of little minds", Emerson)
>
>
> This email is (a) to highlight the plan, and (b) to ask about flags.  Our
> preferred approach is to *change* what -XTypeOperators does, to allow type
> operators that do not start with :.  But that will mean that *some*
> (strange) programs will stop working. The only example I have seen in tc192
> of GHC's test suite
> {-# LANGUAGE TypeOperators #-}
> comp :: Arrow (~>) => (b~>c, c~>d)~>(b~>d)
>   comp = arr (uncurry (>>>))
>
> Written more conventionally, the signature would look like
> comp :: Arrow arr => arr (arr b c, arr c d) (arr b d)
>   comp = arr (uncurry (>>>))
> or, in infix notation
> {-# LANGUAGE TypeOperators #-}
> comp :: Arrow arr => (b `arr` c, c `arr` d) `arr` (b `arr` d)
>   comp = arr (uncurry (>>>))
>
> But tc192 as it stands would become ILLEGAL, because (~>) would be a type
> *constructor* rather than (as now) a type *variable*.  Of course it's easily
> fixed, as above, but still a breakage is a breakage.
>
> It would be possible to have two flags, so as to get
>   - Haskell 98 behaviour
>   - Current TypeOperator behaviuor
>   - New TypeOperator behaviour
> but it turns out to be Quite Tiresome to do so, and I would much rather not.
> Can you live with that?
>
>
> http://chrisdone.com/posts/2010-10-07-haskelldb-and-typeoperator-madness.html
>
>
> ___
> 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-cafe] Call to arms: lambda-case is stuck and needs your help

2012-07-12 Thread Cale Gibbard
There are of course already lots of ways to create functions which
don't involve \

I mentioned sections (like (+1) desugaring to (\x -> x + 1)) already,
and of course, one can partially apply or compose and transform other
functions without explicit lambdas.

We're not exactly talking about function definitions, so much as
expressions whose value happens to be a function. The point is just
that there are already a few other places in the syntax where the
omission of a value results in a function having the omitted value as
its parameter. At least to me, it seems natural to extend that pattern
in this case.

On 12 July 2012 15:03, Daniel Trstenjak  wrote:
>
> On Thu, Jul 12, 2012 at 01:38:56PM -0400, Cale Gibbard wrote:
>> Personally I don't see why everyone appears to prefer the syntax with
>> \ in it over just the obvious case section syntax which was originally
>> proposed.
>
> I don't think that the 'case section syntax' is obvious, because I don't
> see the similarity between a function definition and a partial function
> application.
>
> Always using '\' would be a visual hint for a function definition.
>
>
> Greetings,
> Daniel

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


Re: [Haskell-cafe] Call to arms: lambda-case is stuck and needs your help

2012-07-12 Thread Cale Gibbard
Personally I don't see why everyone appears to prefer the syntax with
\ in it over just the obvious case section syntax which was originally
proposed.

case of { ... }

looks much better to me than

\case of { ... }

and the former makes sense to me as a simple extension of operator
sections to another part of the syntax.

Does anyone else agree?

On 6 July 2012 20:40, Chris Smith  wrote:
> Whoops, my earlier answer forgot to copy mailing lists... I would love to
> see \of, but I really don't think this is important enough to make case
> sometimes introduce layout and other times not.  If it's going to obfuscate
> the lexical syntax like that, I'd rather just stick with \x->case x of.
>
> On Jul 6, 2012 3:15 PM, "Strake"  wrote:
>>
>> On 05/07/2012, Mikhail Vorozhtsov  wrote:
>> > Hi.
>> >
>> > After 21 months of occasional arguing the lambda-case proposal(s) is in
>> > danger of being buried under its own trac ticket comments. We need fresh
>> > blood to finally reach an agreement on the syntax. Read the wiki
>> > page[1], take a look at the ticket[2], vote and comment on the
>> > proposals!
>> >
>>
>> +1 for "\ of" multi-clause lambdas
>>
>> It looks like binding "of" to me, which it ain't, but it is nicely
>> brief...
>>
>> ___
>> Haskell-Cafe mailing list
>> haskell-c...@haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
> ___
> Haskell-Cafe mailing list
> haskell-c...@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>

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