Type Level "Application" Operator

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

+1 from me, if only as a nice-to-have—it would be good to flesh out some
standard type operators in general.
On Nov 1, 2016 4:14 PM, "Elliot Cameron"
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@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

+1! Readability improvements are wonderful.
On Tue, Nov 1, 2016 at 11:31 PM, Jon Purdy
+1 from me, if only as a nice-to-have—it would be good to flesh out some standard type operators in general.
On Nov 1, 2016 4:14 PM, "Elliot Cameron"
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@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
-- Jeff Brown | Jeffrey Benjamin Brown Website https://msu.edu/~brown202/ | Facebook https://www.facebook.com/mejeff.younotjeff | LinkedIn https://www.linkedin.com/in/jeffreybenjaminbrown(I often miss messages here) | Github https://github.com/jeffreybenjaminbrown

+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
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@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

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
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
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@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Edward, I had the exact same thought but I couldn't get it to work. Oddly enough, I actually copied and pasted that example from my code which builds and runs perfectly well. It seems that monad transformers work differently when defined as a type (instead of newtype, which would require me to include the type parameter)? Somewhat related is the question of how to actually *export* this type alias from a module.
module Money (($)) where
type f $ x = f x infixr 0 $
doesn't work because it tries to export Prelude.$. The only way around it
is to import Prelude hiding (($)). But this makes me wonder, is it actually
*impossible* in Haskell to export from the same module a function with the
same name at both the value and type level? Is it possible to export only
one of the two?
Elliot
On Wed, Nov 2, 2016 at 10:42 AM, Oleg Grenrus
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
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
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@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

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
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
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
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@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Edward, I don't quite follow why you think that (.) is needed here.
Monad transformers take two parameters, so your example is not
type-correct, whereas the original one is.
On Wed, Nov 2, 2016 at 5:24 PM, Edward Kmett
+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
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@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

On Wed, Nov 2, 2016 at 3:11 PM, Index Int
Edward, I don't quite follow why you think that (.) is needed here. Monad transformers take two parameters, so your example is not type-correct, whereas the original one is.
Indeed, I appear to have hyper-corrected that example.
-Edward
On Wed, Nov 2, 2016 at 5:24 PM, Edward Kmett
+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
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@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Wouldn't there also be a problem with type unification? When unifying ((f
. g) a) and (h b) do you set ((f . g) ~ h) or ((g a) ~ b)?
On Nov 2, 2016 6:28 PM, "Edward Kmett"
On Wed, Nov 2, 2016 at 3:11 PM, Index Int
wrote: Edward, I don't quite follow why you think that (.) is needed here. Monad transformers take two parameters, so your example is not type-correct, whereas the original one is.
Indeed, I appear to have hyper-corrected that example.
-Edward
On Wed, Nov 2, 2016 at 5:24 PM, Edward Kmett
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
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@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Even with "ReallyLiberalTypeSynonyms" you can't have (f . g) ~ h as that
would involve a partial application in a non type synonym, so there is no
issue with unification.
(.) only means something with all 3 arguments applied so that it can be
expanded, but you can still allow it to be formally passed around inside
other type synonyms so long as the final type synonym has all of its
arguments expanded.
type (.) f g x = f (g x)
type Foo = (.) Bar
Foo doesn't fully instantiate (.) but you can keep eta expanding it until
it does.
type Foo g x = (.) Bar g x = Bar (g x)
is a perfectly legitimate definition. You can do this expansion
automatically pretty easily. Given such a type synonym you can answer how
many arguments it must have before it is a real type.
At a use site Foo is not a type until it has been applied to two more
arguments, just like the eta expanded form above. Foo ~ Baz doesn't type
check for the same reason given
type Id a = a
you can't talk about Id ~ Bar. Id isn't a type. It needs an argument before
it makes sense.
This is what I mean by "ReallyLiberalTypeSynonyms". We actually wound up
with these by accident in the Ermine compiler we use at work, and they
turned out to be quite useful and harmless in practice.
We don't have this power today, but we do have LiberalTypeSynonyms, which
gets us close.
-Edward
On Wed, Nov 2, 2016 at 7:36 PM, Ken Bateman
Wouldn't there also be a problem with type unification? When unifying ((f . g) a) and (h b) do you set ((f . g) ~ h) or ((g a) ~ b)?
On Nov 2, 2016 6:28 PM, "Edward Kmett"
wrote: On Wed, Nov 2, 2016 at 3:11 PM, Index Int
wrote: Edward, I don't quite follow why you think that (.) is needed here. Monad transformers take two parameters, so your example is not type-correct, whereas the original one is.
Indeed, I appear to have hyper-corrected that example.
-Edward
On Wed, Nov 2, 2016 at 5:24 PM, Edward Kmett
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
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@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
participants (7)
-
Edward Kmett
-
Elliot Cameron
-
Index Int
-
Jeffrey Brown
-
Jon Purdy
-
Ken Bateman
-
Oleg Grenrus