Type Level "Application" Operator

Edward Kmett ekmett at gmail.com
Wed Nov 2 16:35:12 UTC 2016


To make . work, we'd need both the ability to parse . at the type level without the compiler flipping out and assuming it is part of a rank n signature (which was the first issue I was trying to mention) and a form of "Really LiberalTypeSynonyms" like we use in ermine to allow the partial application so long as App is only used applied to an argument.

In theory non recursive partial application of type synonyms within a type synonym is perfectly admissible in Haskell type checking, it just complicates the expansion and we don't do it today.

Both are solvable, but are nowhere near the low hanging fruit that adding $ would be.

-Edward

> On Nov 2, 2016, at 10:42 AM, Oleg Grenrus <oleg.grenrus at iki.fi> wrote:
> 
> To make it clear:
> 
> type level `.` won’t work as an type synonym, as it’s application isn’t saturated.
> 
> {-# LANGUAGE TypeOperators #-}
> type (:.:) f g x = f (g x)
> infixr 9 :.:
> 
> type App = Maybe :.: []
> 
> fails to compile with following errors (for a reason):
> 
>    • The type synonym ‘:.:’ should have 3 arguments, but has been given 2
>    • In the type synonym declaration for ‘App’
> 
>> On 02 Nov 2016, at 16:24, Edward Kmett <ekmett at gmail.com> wrote:
>> 
>> +1, but the operator you're looking for in App there would actually be a type level version of (.).
>> 
>> type App a = ExceptT Err $ ReaderT Config $ LogT Text $ IO a
>> 
>> type App = ExceptT Err . ReaderT Config . LogT Text . IO
>> 
>> which would need
>> 
>> type (.) f g x = f (g x)
>> infixr 9 .
>> 
>> to parse
>> 
>> -Edward
>> 
>> On Tue, Nov 1, 2016 at 7:13 PM, Elliot Cameron <eacameron at gmail.com> wrote:
>> Folks,
>> 
>> Has there been a discussion about adding a type-level operator "$" that just mimics "$" at the value level?
>> 
>> type f $ x = f x
>> infixr 0 $
>> 
>> Things like monad transformer stacks would look more "stack-like" with this:
>> 
>> type App = ExceptT Err $ ReaderT Config $ LogT Text IO
>> 
>> Elliot Cameron
>> 
>> _______________________________________________
>> Libraries mailing list
>> Libraries at haskell.org
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
>> 
>> 
>> _______________________________________________
>> Libraries mailing list
>> Libraries at haskell.org
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
> 
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/libraries/attachments/20161102/0136c43f/attachment.html>


More information about the Libraries mailing list