
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