Proposal: merge either into transformers

I propose to add the sole module of the 'either' package[1], Control.Monad.Trans.Either, to the transformers package. It provides EitherT, a very basic and fundamental data type. The difference between EitherT and ErrorT is that the latter has an Error constraint, which is used to imlement 'fail'. Note that 'either' depends on the 'semigroupoids' and 'semigroup' packages to provide appropriate instances. The proposal is not to add those instances to 'transformers' to avoid additional dependencies. The instances can then be left in the 'either' package or moved to the 'semigroupoids' and 'semigroup' packages respectively. ('semigroupoids' already depends on 'transformers', while 'semigroups' does not). Compared to the 'either' package, Show, Read, Eq and Ord instances will be dropped to keep the code Haskell2010 (those instances require FlexibleInstances, FlexibleContexts, and UndecidableInstances). The patch is attached. [*] [*] against transformers-0.3.0.0, because the darcs version is not buildable (Control/Monad/Signatures.hs is not in the repository). Roman

On Fri, Dec 7, 2012 at 11:44 AM, Roman Cheplyaka
I propose to add the sole module of the 'either' package[1], Control.Monad.Trans.Either, to the transformers package.
It provides EitherT, a very basic and fundamental data type. The difference between EitherT and ErrorT is that the latter has an Error constraint, which is used to imlement 'fail'.
Note that 'either' depends on the 'semigroupoids' and 'semigroup' packages to provide appropriate instances. The proposal is not to add those instances to 'transformers' to avoid additional dependencies. The instances can then be left in the 'either' package or moved to the 'semigroupoids' and 'semigroup' packages respectively. ('semigroupoids' already depends on 'transformers', while 'semigroups' does not).
Compared to the 'either' package, Show, Read, Eq and Ord instances will be dropped to keep the code Haskell2010 (those instances require FlexibleInstances, FlexibleContexts, and UndecidableInstances).
The patch is attached. [*]
[*] against transformers-0.3.0.0, because the darcs version is not buildable (Control/Monad/Signatures.hs is not in the repository).
Roman
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
+1 Michael

I will be sad to see those instances go, but I'm also +1
On Fri, Dec 7, 2012 at 7:55 AM, Gregory Collins
On Fri, Dec 7, 2012 at 10:44 AM, Roman Cheplyaka
wrote: I propose to add the sole module of the 'either' package[1], Control.Monad.Trans.Either, to the transformers package.
+1 -- Gregory Collins
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On Fri, 7 Dec 2012, Edward Kmett wrote:
I will be sad to see those instances go, but I'm also +1
How about: import Prelude hiding (Show, showsPrec) import qualified Prelude as P class Show m where showsPrec :: (P.Show e, P.Show a) => Int -> m (Either e a) -> ShowS instance (Show m, P.Show e, P.Show a) => P.Show (EitherT e m a) where showsPrec d (EitherT m) = showParen (d > 10) $ showString "EitherT " . showsPrec 11 m and so on for Read, Eq, Ord?

On Sat, Dec 08, 2012 at 10:55:45PM +0000, Henning Thielemann wrote:
On Fri, 7 Dec 2012, Edward Kmett wrote:
I will be sad to see those instances go, but I'm also +1
How about:
import Prelude hiding (Show, showsPrec) import qualified Prelude as P
class Show m where showsPrec :: (P.Show e, P.Show a) => Int -> m (Either e a) -> ShowS
instance (Show m, P.Show e, P.Show a) => P.Show (EitherT e m a) where showsPrec d (EitherT m) = showParen (d > 10) $ showString "EitherT " . showsPrec 11 m
A more economical variation on this idea would be to lift these classes to functors, e.g. class ShowF f where showsPrecF :: Show a => Int -> f a -> ShowS instance (ShowF m, Show e, Show a) => Show (EitherT e m a) where showsPrec d (EitherT m) = showParen (d > 10) $ showString "EitherT " . showsPrecF 11 m instance (ShowF m, Show e) => ShowF (EitherT e m) where showsPrecF = showsPrec

I have a prelude-extras package that I use for 'bound' which contains those Eq1, Show1, etc classes.
(As an unrelated aside bound packages up the generalized de Bruijn indices you did with Hinze as a reusable Haskell 98 monad transformer, you may find it interesting.)
Sent from my iPhone
On Dec 8, 2012, at 8:24 PM, Ross Paterson
On Sat, Dec 08, 2012 at 10:55:45PM +0000, Henning Thielemann wrote:
On Fri, 7 Dec 2012, Edward Kmett wrote:
I will be sad to see those instances go, but I'm also +1
How about:
import Prelude hiding (Show, showsPrec) import qualified Prelude as P
class Show m where showsPrec :: (P.Show e, P.Show a) => Int -> m (Either e a) -> ShowS
instance (Show m, P.Show e, P.Show a) => P.Show (EitherT e m a) where showsPrec d (EitherT m) = showParen (d > 10) $ showString "EitherT " . showsPrec 11 m
A more economical variation on this idea would be to lift these classes to functors, e.g.
class ShowF f where showsPrecF :: Show a => Int -> f a -> ShowS
instance (ShowF m, Show e, Show a) => Show (EitherT e m a) where showsPrec d (EitherT m) = showParen (d > 10) $ showString "EitherT " . showsPrecF 11 m
instance (ShowF m, Show e) => ShowF (EitherT e m) where showsPrecF = showsPrec
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On Sun, Dec 09, 2012 at 01:38:59AM +0000, Edward A Kmett wrote:
I have a prelude-extras package that I use for 'bound' which contains those Eq1, Show1, etc classes.
OK, then if me move Eq1, Ord1, Show1 and Read1 into transformers with a bunch of instances we can keep these instances for EitherT (and define some more).
(As an unrelated aside bound packages up the generalized de Bruijn indices you did with Hinze as a reusable Haskell 98 monad transformer, you may find it interesting.)
You mean Richard Bird, of course.

On Sat, Dec 8, 2012 at 9:00 PM, Ross Paterson
OK, then if me move Eq1, Ord1, Show1 and Read1 into transformers with a bunch of instances we can keep these instances for EitherT (and define some more).
I would definitely be +1 on the move. It would get a lot more instances than having them rotting off in a side-package of mine somewhere. I could probably then retire the package as I don't use the '2' variants very often.
(As an unrelated aside bound packages up the generalized de Bruijn indices you did with Hinze as a reusable Haskell 98 monad transformer, you may find it interesting.)
You mean Richard Bird, of course.
Indeed I do. -Edward

On Sun, Dec 09, 2012 at 01:24:36AM +0000, Ross Paterson wrote:
A more economical variation on this idea would be to lift these classes to functors, e.g.
class ShowF f where showsPrecF :: Show a => Int -> f a -> ShowS
instance (ShowF m, Show e, Show a) => Show (EitherT e m a) where showsPrec d (EitherT m) = showParen (d > 10) $ showString "EitherT " . showsPrecF 11 m
instance (ShowF m, Show e) => ShowF (EitherT e m) where showsPrecF = showsPrec
To also lift Prelude classes like Show to Compose (which seems desirable), we'd need to use an explicit dictionary instead: class ShowF f where showsPrecF :: (Int -> a -> ShowS) -> Int -> f a -> ShowS instance (ShowF f, ShowF g) => ShowF (Compose f g) where showsPrecF sp d (Compose x) = showParen (d > 10) $ showString "Compose " . showsPrecF (showsPrecF sp) 11 x instance (ShowF f, ShowF g, Show a) => Show (Compose f g a) where showsPrec = showsPrecF showsPrec

On Wed, 12 Dec 2012, Ross Paterson wrote:
On Sun, Dec 09, 2012 at 01:24:36AM +0000, Ross Paterson wrote:
A more economical variation on this idea would be to lift these classes to functors, e.g.
class ShowF f where showsPrecF :: Show a => Int -> f a -> ShowS
instance (ShowF m, Show e, Show a) => Show (EitherT e m a) where showsPrec d (EitherT m) = showParen (d > 10) $ showString "EitherT " . showsPrecF 11 m
instance (ShowF m, Show e) => ShowF (EitherT e m) where showsPrecF = showsPrec
To also lift Prelude classes like Show to Compose (which seems desirable), we'd need to use an explicit dictionary instead:
class ShowF f where showsPrecF :: (Int -> a -> ShowS) -> Int -> f a -> ShowS
instance (ShowF f, ShowF g) => ShowF (Compose f g) where showsPrecF sp d (Compose x) = showParen (d > 10) $ showString "Compose " . showsPrecF (showsPrecF sp) 11 x
instance (ShowF f, ShowF g, Show a) => Show (Compose f g a) where showsPrec = showsPrecF showsPrec
If you tolerate a (Functor f) constraint you may use a helper type, that lifts (ShowF f, Show a) to (Show (f a)): class ShowF f where showsPrecF :: (Show a) => Int -> f a -> ShowS newtype Inner g a = Inner (g a) instance (ShowF g, Show a) => Show (Inner g a) where showsPrec p (Inner g) = showsPrecF p g instance (Functor f, ShowF f, ShowF g) => ShowF (Compose f g) where showsPrecF d (Compose x) = showParen (d > 10) $ showString "Compose " . showsPrecF 11 (fmap Inner x) instance (Functor f, ShowF f, ShowF g, Show a) => Show (Compose f g a) where showsPrec = showsPrecF You may also make Functor a superclass of ShowF.

On Wed, Dec 12, 2012 at 05:20:06PM +0000, Henning Thielemann wrote:
On Wed, 12 Dec 2012, Ross Paterson wrote:
On Sun, Dec 09, 2012 at 01:24:36AM +0000, Ross Paterson wrote:
A more economical variation on this idea would be to lift these classes to functors, e.g.
class ShowF f where showsPrecF :: Show a => Int -> f a -> ShowS
instance (ShowF m, Show e, Show a) => Show (EitherT e m a) where showsPrec d (EitherT m) = showParen (d > 10) $ showString "EitherT " . showsPrecF 11 m
instance (ShowF m, Show e) => ShowF (EitherT e m) where showsPrecF = showsPrec
To also lift Prelude classes like Show to Compose (which seems desirable), we'd need to use an explicit dictionary instead:
class ShowF f where showsPrecF :: (Int -> a -> ShowS) -> Int -> f a -> ShowS
instance (ShowF f, ShowF g) => ShowF (Compose f g) where showsPrecF sp d (Compose x) = showParen (d > 10) $ showString "Compose " . showsPrecF (showsPrecF sp) 11 x
instance (ShowF f, ShowF g, Show a) => Show (Compose f g a) where showsPrec = showsPrecF showsPrec
If you tolerate a (Functor f) constraint you may use a helper type, that lifts (ShowF f, Show a) to (Show (f a)):
class ShowF f where showsPrecF :: (Show a) => Int -> f a -> ShowS
newtype Inner g a = Inner (g a)
instance (ShowF g, Show a) => Show (Inner g a) where showsPrec p (Inner g) = showsPrecF p g
instance (Functor f, ShowF f, ShowF g) => ShowF (Compose f g) where showsPrecF d (Compose x) = showParen (d > 10) $ showString "Compose " . showsPrecF 11 (fmap Inner x)
instance (Functor f, ShowF f, ShowF g, Show a) => Show (Compose f g a) where showsPrec = showsPrecF
Doing an fmap just to make an instance work is pretty unpleasant, but having to hand-write all the instances, as the explicit dictionary version would require, is probably worse.
You may also make Functor a superclass of ShowF.
I'm not sure about that -- one might want to make Set an instance. Assuming we have Eq1, Ord1, Show1 and Read1, what would be a good name for the module defining them?

On Sun, 16 Dec 2012, Ross Paterson wrote:
Doing an fmap just to make an instance work is pretty unpleasant, but having to hand-write all the instances, as the explicit dictionary version would require, is probably worse.
You may also make Functor a superclass of ShowF.
I'm not sure about that -- one might want to make Set an instance.
Right.
Assuming we have Eq1, Ord1, Show1 and Read1, what would be a good name for the module defining them?
Data.Functor.Class ? Ok, Set is not a Functor. :-(

On Fri, Dec 07, 2012 at 09:44:27AM +0000, Roman Cheplyaka wrote:
I propose to add the sole module of the 'either' package[1], Control.Monad.Trans.Either, to the transformers package.
It provides EitherT, a very basic and fundamental data type. The difference between EitherT and ErrorT is that the latter has an Error constraint, which is used to imlement 'fail'.
Note that 'either' depends on the 'semigroupoids' and 'semigroup' packages to provide appropriate instances. The proposal is not to add those instances to 'transformers' to avoid additional dependencies. The instances can then be left in the 'either' package or moved to the 'semigroupoids' and 'semigroup' packages respectively. ('semigroupoids' already depends on 'transformers', while 'semigroups' does not).
Orphan instances are to be avoided, so moving the instances to those packages seems the only option.
Compared to the 'either' package, Show, Read, Eq and Ord instances will be dropped to keep the code Haskell2010 (those instances require FlexibleInstances, FlexibleContexts, and UndecidableInstances).
That's true. Some other points: The either package has mapEitherT as the binary map mapEitherT :: Functor m => (e -> f) -> (a -> b) -> EitherT e m a -> EitherT f m b but consistency with the rest of transformers would apply this name to mapEitherT :: (m (Either e a) -> n (Either e' b)) -> EitherT e m a -> EitherT e' n b mapEitherT f m = EitherT $ f (runEitherT m) (The binary map can't be recovered using Bifunctor because of the argument order.) either has hoistEither :: Monad m => Either e a -> EitherT e m a Maybe transformers should have similar functions for all the other monad transformers. left and right are used with different meanings in Control.Arrow (surmountable with qualification, of course). I see that the idea is to be symmetrical, but the monad structure is asymmetric. Would we want a catch function?

On Fri, Dec 7, 2012 at 12:45 PM, Ross Paterson
On Fri, Dec 07, 2012 at 09:44:27AM +0000, Roman Cheplyaka wrote:
I propose to add the sole module of the 'either' package[1], Control.Monad.Trans.Either, to the transformers package.
It provides EitherT, a very basic and fundamental data type. The difference between EitherT and ErrorT is that the latter has an Error constraint, which is used to imlement 'fail'.
Note that 'either' depends on the 'semigroupoids' and 'semigroup' packages to provide appropriate instances. The proposal is not to add those instances to 'transformers' to avoid additional dependencies. The instances can then be left in the 'either' package or moved to the 'semigroupoids' and 'semigroup' packages respectively. ('semigroupoids' already depends on 'transformers', while 'semigroups' does not).
Orphan instances are to be avoided, so moving the instances to those packages seems the only option.
Sure. I'd be happy to invert the dependencies. As I wrote semigroups, semigroupoids and either in the first place. ;)
Compared to the 'either' package, Show, Read, Eq and Ord instances will be dropped to keep the code Haskell2010 (those instances require FlexibleInstances, FlexibleContexts, and UndecidableInstances).
That's true. Some other points:
The either package has mapEitherT as the binary map
mapEitherT :: Functor m => (e -> f) -> (a -> b) -> EitherT e m a -> EitherT f m b
but consistency with the rest of transformers would apply this name to
mapEitherT :: (m (Either e a) -> n (Either e' b)) -> EitherT e m a -> EitherT e' n b mapEitherT f m = EitherT $ f (runEitherT m)
Something that provides the existing 'mapEitherT' functionality would be nice to retain as it gets used in multiple packages. Perhaps bikeshed it to 'bimapEitherT', and use 'mapEitherT' for your notion?
(The binary map can't be recovered using Bifunctor because of the argument order.)
either has
hoistEither :: Monad m => Either e a -> EitherT e m a
Maybe transformers should have similar functions for all the other monad transformers.
+1 I would really like this. left and right are used with different meanings in Control.Arrow
(surmountable with qualification, of course). I see that the idea is to be symmetrical, but the monad structure is asymmetric.
I'm not wedded to the names of the 'left' and 'right' combinators in 'either'. The functionality would be nice to retain, but the names I'm completely indifferent to.
Would we want a catch function?
It probably wouldn't hurt. -Edward

On 12/7/12 1:01 PM, Edward Kmett wrote:
On Fri, Dec 7, 2012 at 12:45 PM, Ross Paterson
wrote: The either package has mapEitherT as the binary map
mapEitherT :: Functor m => (e -> f) -> (a -> b) -> EitherT e m a -> EitherT f m b
but consistency with the rest of transformers would apply this name to
mapEitherT :: (m (Either e a) -> n (Either e' b)) -> EitherT e m a -> EitherT e' n b mapEitherT f m = EitherT $ f (runEitherT m)
Something that provides the existing 'mapEitherT' functionality would be nice to retain as it gets used in multiple packages. Perhaps bikeshed it to 'bimapEitherT', and use 'mapEitherT' for your notion?
+1 for bimapEitherT -- Live well, ~wren

+1 deprecate the either package, and try to find a home for those orphans. -- Dan Burton

Roman Cheplyaka
writes:
I propose to add the sole module of the 'either' package[1], Control.Monad.Trans.Either, to the transformers package.
+1 -- John Wiegley FP Complete Haskell tools, training and consulting http://fpcomplete.com johnw on #haskell/irc.freenode.net

On Mon, Dec 10, 2012 at 04:17:23PM +0000, Mario Blažević wrote:
On 12-12-07 04:44 AM, Roman Cheplyaka wrote:
I propose to add the sole module of the 'either' package[1], Control.Monad.Trans.Either, to the transformers package.
+1. Then I can drop the EitherFunctor type from the monad-coroutine package.
That's not the same thing: newtype EitherT e m a = EitherT { runEitherT :: m (Either e a) } data EitherFunctor l r x = LeftF (l x) | RightF (r x)

On 12-12-10 11:35 AM, Ross Paterson wrote:
On Mon, Dec 10, 2012 at 04:17:23PM +0000, Mario Blažević wrote:
On 12-12-07 04:44 AM, Roman Cheplyaka wrote:
I propose to add the sole module of the 'either' package[1], Control.Monad.Trans.Either, to the transformers package.
+1. Then I can drop the EitherFunctor type from the monad-coroutine package.
That's not the same thing:
newtype EitherT e m a = EitherT { runEitherT :: m (Either e a) }
data EitherFunctor l r x = LeftF (l x) | RightF (r x)
I let my hopes run wild. Oh well, I'm still okay with the change. Any chance of having an equivalent of EitherFunctor included in Transformers as well?

There is Data.Functor.Coproduct in comonad-transformers (
http://hackage.haskell.org/packages/archive/comonad-transformers/3.0/doc/htm...)
which could be moved.
I never really liked having it in the comonad-transformers package anyways.
-Edward
On Mon, Dec 10, 2012 at 11:43 AM, Mario Blažević
On 12-12-10 11:35 AM, Ross Paterson wrote:
On Mon, Dec 10, 2012 at 04:17:23PM +0000, Mario Blažević wrote:
On 12-12-07 04:44 AM, Roman Cheplyaka wrote:
I propose to add the sole module of the 'either' package[1], Control.Monad.Trans.Either, to the transformers package.
+1. Then I can drop the EitherFunctor type from the monad-coroutine package.
That's not the same thing:
newtype EitherT e m a = EitherT { runEitherT :: m (Either e a) }
data EitherFunctor l r x = LeftF (l x) | RightF (r x)
I let my hopes run wild. Oh well, I'm still okay with the change. Any chance of having an equivalent of EitherFunctor included in Transformers as well?
______________________________**_________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/**mailman/listinfo/librarieshttp://www.haskell.org/mailman/listinfo/libraries

On 12-12-10 01:57 PM, Edward Kmett wrote:
There is Data.Functor.Coproduct in comonad-transformers (http://hackage.haskell.org/packages/archive/comonad-transformers/3.0/doc/htm...) which could be moved.
I never really liked having it in the comonad-transformers package anyways.
There is also Cgm.Data.Functor.Sum in cognimeta-utils, though it doesn't come with a Functor instance for some reason. I think I prefer Data.Functor.Sum to Data.Functor.Coproduct. There may be more occurrences in Hackage, hiding under less obious names. I presume this addition to Transformers would require a new proposal?

The problem with Data.Functor.Sum is that Data.Monoid exports Sum. While I
don't think we should try to globally avoid all conflicts, I don't think we
should go out of our way to pick up a conflict we don't have to have.
On Mon, Dec 10, 2012 at 4:38 PM, Mario Blažević
On 12-12-10 01:57 PM, Edward Kmett wrote:
There is Data.Functor.Coproduct in comonad-transformers (http://hackage.haskell.org/**packages/archive/comonad-** transformers/3.0/doc/html/**Data-Functor-Coproduct.htmlhttp://hackage.haskell.org/packages/archive/comonad-transformers/3.0/doc/htm... ) which could be moved.
I never really liked having it in the comonad-transformers package anyways.
There is also Cgm.Data.Functor.Sum in cognimeta-utils, though it doesn't come with a Functor instance for some reason. I think I prefer Data.Functor.Sum to Data.Functor.Coproduct. There may be more occurrences in Hackage, hiding under less obious names.
I presume this addition to Transformers would require a new proposal?

On 12-12-10 04:51 PM, Edward Kmett wrote:
The problem with Data.Functor.Sum is that Data.Monoid exports Sum. While I don't think we should try to globally avoid all conflicts, I don't think we should go out of our way to pick up a conflict we don't have to have.
Both Data.Monoid and Data.Functor.Product export a type named Product. I guess you could argue that there was no choice in case of Product, while Sum can be called a Coproduct. That being said, I don't care what the name is as long as it's available from the transforms package. Do you want to push the proposal?
On Mon, Dec 10, 2012 at 4:38 PM, Mario Blažević
mailto:mblazevic@stilo.com> wrote: On 12-12-10 01:57 PM, Edward Kmett wrote:
There is Data.Functor.Coproduct in comonad-transformers (http://hackage.haskell.org/__packages/archive/comonad-__transformers/3.0/doc... http://hackage.haskell.org/packages/archive/comonad-transformers/3.0/doc/htm...) which could be moved.
I never really liked having it in the comonad-transformers package anyways.
There is also Cgm.Data.Functor.Sum in cognimeta-utils, though it doesn't come with a Functor instance for some reason. I think I prefer Data.Functor.Sum to Data.Functor.Coproduct. There may be more occurrences in Hackage, hiding under less obious names.
I presume this addition to Transformers would require a new proposal?
-- Mario Blazevic mblazevic@stilo.com Stilo International This message, including any attachments, is for the sole use of the intended recipient(s) and may contain confidential and privileged information. Any unauthorized review, use, disclosure, copying, or distribution is strictly prohibited. If you are not the intended recipient(s) please contact the sender by reply email and destroy all copies of the original message and any attachments.

If you make the proposal, i'll happily +1 it ;)
On Mon, Dec 10, 2012 at 5:07 PM, Mario Blažević
On 12-12-10 04:51 PM, Edward Kmett wrote:
The problem with Data.Functor.Sum is that Data.Monoid exports Sum. While I don't think we should try to globally avoid all conflicts, I don't think we should go out of our way to pick up a conflict we don't have to have.
Both Data.Monoid and Data.Functor.Product export a type named Product. I guess you could argue that there was no choice in case of Product, while Sum can be called a Coproduct.
That being said, I don't care what the name is as long as it's available from the transforms package. Do you want to push the proposal?
On Mon, Dec 10, 2012 at 4:38 PM, Mario Blažević
mailto:mblazevic@stilo.com> wrote: On 12-12-10 01:57 PM, Edward Kmett wrote:
There is Data.Functor.Coproduct in comonad-transformers (http://hackage.haskell.org/__**packages/archive/comonad-__** transformers/3.0/doc/html/__**Data-Functor-Coproduct.htmlhttp://hackage.haskell.org/__packages/archive/comonad-__transformers/3.0/doc... <http://hackage.haskell.org/**packages/archive/comonad-** transformers/3.0/doc/html/**Data-Functor-Coproduct.htmlhttp://hackage.haskell.org/packages/archive/comonad-transformers/3.0/doc/htm...
)
which could be moved.
I never really liked having it in the comonad-transformers package anyways.
There is also Cgm.Data.Functor.Sum in cognimeta-utils, though it doesn't come with a Functor instance for some reason. I think I prefer Data.Functor.Sum to Data.Functor.Coproduct. There may be more occurrences in Hackage, hiding under less obious names.
I presume this addition to Transformers would require a new proposal?
-- Mario Blazevic mblazevic@stilo.com Stilo International
This message, including any attachments, is for the sole use of the intended recipient(s) and may contain confidential and privileged information. Any unauthorized review, use, disclosure, copying, or distribution is strictly prohibited. If you are not the intended recipient(s) please contact the sender by reply email and destroy all copies of the original message and any attachments.

On 2012-12-07 09:44, Roman Cheplyaka wrote:
I propose to add the sole module of the 'either' package[1], Control.Monad.Trans.Either, to the transformers package.
It provides EitherT, a very basic and fundamental data type. The difference between EitherT and ErrorT is that the latter has an Error constraint, which is used to imlement 'fail'.
Note that 'either' depends on the 'semigroupoids' and 'semigroup' packages to provide appropriate instances. The proposal is not to add those instances to 'transformers' to avoid additional dependencies. The instances can then be left in the 'either' package or moved to the 'semigroupoids' and 'semigroup' packages respectively. ('semigroupoids' already depends on 'transformers', while 'semigroups' does not).
Compared to the 'either' package, Show, Read, Eq and Ord instances will be dropped to keep the code Haskell2010 (those instances require FlexibleInstances, FlexibleContexts, and UndecidableInstances).
The patch is attached. [*]
[*] against transformers-0.3.0.0, because the darcs version is not buildable (Control/Monad/Signatures.hs is not in the repository).
[Sorry to revive this 1 yr 1/2 thread, but I was looking at the reason why we don't have eitherT is a more canonical place like transformers, and ended up here ...] Is there a reason why this thread ran out of steam ? It not totally obvious from the answers what was missing to move forward. It seems like there's general agreement that EitherT is a good addition, did this proposal got forgotten ? Is there a way to revive this proposal ? Cheers, -- Vincent

* Vincent Hanquez
On 2012-12-07 09:44, Roman Cheplyaka wrote:
I propose to add the sole module of the 'either' package[1], Control.Monad.Trans.Either, to the transformers package.
It provides EitherT, a very basic and fundamental data type. The difference between EitherT and ErrorT is that the latter has an Error constraint, which is used to imlement 'fail'.
Note that 'either' depends on the 'semigroupoids' and 'semigroup' packages to provide appropriate instances. The proposal is not to add those instances to 'transformers' to avoid additional dependencies. The instances can then be left in the 'either' package or moved to the 'semigroupoids' and 'semigroup' packages respectively. ('semigroupoids' already depends on 'transformers', while 'semigroups' does not).
Compared to the 'either' package, Show, Read, Eq and Ord instances will be dropped to keep the code Haskell2010 (those instances require FlexibleInstances, FlexibleContexts, and UndecidableInstances).
The patch is attached. [*]
[*] against transformers-0.3.0.0, because the darcs version is not buildable (Control/Monad/Signatures.hs is not in the repository).
[Sorry to revive this 1 yr 1/2 thread, but I was looking at the reason why we don't have eitherT is a more canonical place like transformers, and ended up here ...]
Is there a reason why this thread ran out of steam ? It not totally obvious from the answers what was missing to move forward. It seems like there's general agreement that EitherT is a good addition, did this proposal got forgotten ? Is there a way to revive this proposal ?
IIRC, last time this was brought up, Ross said that he'd take action after GHC 7.8 is released. So your reminder is well timed, in fact ;) Roman

On 2014-04-24 16:14, Roman Cheplyaka wrote:
IIRC, last time this was brought up, Ross said that he'd take action after GHC 7.8 is released. So your reminder is well timed, in fact ;) Great. Do you have any pointer to this discussion, if any ? I don't understand why would it be linked to ghc's releases though.
-- Vincent

* Vincent Hanquez
On 2014-04-24 16:14, Roman Cheplyaka wrote:
IIRC, last time this was brought up, Ross said that he'd take action after GHC 7.8 is released. So your reminder is well timed, in fact ;) Great. Do you have any pointer to this discussion, if any ?
No, unfortunately I can't find it now.
I don't understand why would it be linked to ghc's releases though.
Neither did I, but the resolution was good enough for me. Roman

On Thu, Apr 24, 2014 at 06:14:48PM +0300, Roman Cheplyaka wrote:
* Vincent Hanquez
[2014-04-24 15:45:34+0100] On 2012-12-07 09:44, Roman Cheplyaka wrote:
I propose to add the sole module of the 'either' package[1], Control.Monad.Trans.Either, to the transformers package.
It provides EitherT, a very basic and fundamental data type. The difference between EitherT and ErrorT is that the latter has an Error constraint, which is used to imlement 'fail'.
Note that 'either' depends on the 'semigroupoids' and 'semigroup' packages to provide appropriate instances. The proposal is not to add those instances to 'transformers' to avoid additional dependencies. The instances can then be left in the 'either' package or moved to the 'semigroupoids' and 'semigroup' packages respectively. ('semigroupoids' already depends on 'transformers', while 'semigroups' does not).
Compared to the 'either' package, Show, Read, Eq and Ord instances will be dropped to keep the code Haskell2010 (those instances require FlexibleInstances, FlexibleContexts, and UndecidableInstances).
The patch is attached. [*]
[*] against transformers-0.3.0.0, because the darcs version is not buildable (Control/Monad/Signatures.hs is not in the repository).
[Sorry to revive this 1 yr 1/2 thread, but I was looking at the reason why we don't have eitherT is a more canonical place like transformers, and ended up here ...]
Is there a reason why this thread ran out of steam ? It not totally obvious from the answers what was missing to move forward. It seems like there's general agreement that EitherT is a good addition, did this proposal got forgotten ? Is there a way to revive this proposal ?
IIRC, last time this was brought up, Ross said that he'd take action after GHC 7.8 is released. So your reminder is well timed, in fact ;)
Instead of EitherT, the next version will deprecate ErrorT in favour of a transformer ExceptT with base monad Except. The idea is to have analogous transformers and monads ExceptT : Except : Either WriterT : Writer : (,) ReaderT : Reader : (->) Other changes are: * Added infixr 9 `Compose` to match (.) * Added Eq, Ord, Read and Show instances where possible * Replaced record syntax for newtypes with separate inverse functions * Added delimited continuation functions to ContT * Added instance Alternative IO to ErrorT Pre-release docs are here: http://code.haskell.org/~ross/transformers/dist/doc/html/transformers/

If you let me know when you want to ship it, I can have a version of the
mtl ready to sit on top.
-Edward
On Fri, Apr 25, 2014 at 8:21 PM, Ross Paterson
On Thu, Apr 24, 2014 at 06:14:48PM +0300, Roman Cheplyaka wrote:
* Vincent Hanquez
[2014-04-24 15:45:34+0100] On 2012-12-07 09:44, Roman Cheplyaka wrote:
I propose to add the sole module of the 'either' package[1], Control.Monad.Trans.Either, to the transformers package.
It provides EitherT, a very basic and fundamental data type. The difference between EitherT and ErrorT is that the latter has an Error constraint, which is used to imlement 'fail'.
Note that 'either' depends on the 'semigroupoids' and 'semigroup' packages to provide appropriate instances. The proposal is not to add those instances to 'transformers' to avoid additional dependencies. The instances can then be left in the 'either' package or moved to the 'semigroupoids' and 'semigroup' packages respectively. ('semigroupoids' already depends on 'transformers', while 'semigroups' does not).
Compared to the 'either' package, Show, Read, Eq and Ord instances will be dropped to keep the code Haskell2010 (those instances require FlexibleInstances, FlexibleContexts, and UndecidableInstances).
The patch is attached. [*]
[*] against transformers-0.3.0.0, because the darcs version is not buildable (Control/Monad/Signatures.hs is not in the repository).
[Sorry to revive this 1 yr 1/2 thread, but I was looking at the reason why we don't have eitherT is a more canonical place like transformers, and ended up here ...]
Is there a reason why this thread ran out of steam ? It not totally obvious from the answers what was missing to move forward. It seems like there's general agreement that EitherT is a good addition, did this proposal got forgotten ? Is there a way to revive this proposal ?
IIRC, last time this was brought up, Ross said that he'd take action after GHC 7.8 is released. So your reminder is well timed, in fact ;)
Instead of EitherT, the next version will deprecate ErrorT in favour of a transformer ExceptT with base monad Except. The idea is to have analogous transformers and monads
ExceptT : Except : Either WriterT : Writer : (,) ReaderT : Reader : (->)
Other changes are:
* Added infixr 9 `Compose` to match (.) * Added Eq, Ord, Read and Show instances where possible * Replaced record syntax for newtypes with separate inverse functions * Added delimited continuation functions to ContT * Added instance Alternative IO to ErrorT
Pre-release docs are here:
http://code.haskell.org/~ross/transformers/dist/doc/html/transformers/ _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

* Ross Paterson
Instead of EitherT, the next version will deprecate ErrorT in favour of a transformer ExceptT with base monad Except. The idea is to have analogous transformers and monads
ExceptT : Except : Either WriterT : Writer : (,) ReaderT : Reader : (->)
Great! When do you plan to make a release?
Pre-release docs are here:
http://code.haskell.org/~ross/transformers/dist/doc/html/transformers/
The docs for Control.Monad.Trans.Writer.Strict say:
Although the output is built strictly, it is not possible to achieve linear space behaviour with this transformer: for that, use Control.Monad.Trans.State.Strict instead.
I think it should be "constant", not "linear". Roman

On Sat, Apr 26, 2014 at 09:16:57AM +0300, Roman Cheplyaka wrote:
* Ross Paterson
[2014-04-26 01:21:09+0100] Instead of EitherT, the next version will deprecate ErrorT in favour of a transformer ExceptT with base monad Except. The idea is to have analogous transformers and monads
ExceptT : Except : Either WriterT : Writer : (,) ReaderT : Reader : (->)
Great! When do you plan to make a release?
Let's say Wednesday, if no-one notices a major problem.
Pre-release docs are here:
http://code.haskell.org/~ross/transformers/dist/doc/html/transformers/
The docs for Control.Monad.Trans.Writer.Strict say:
Although the output is built strictly, it is not possible to achieve linear space behaviour with this transformer: for that, use Control.Monad.Trans.State.Strict instead.
I think it should be "constant", not "linear".
Indeed -- thanks for catching that. I wonder whether the strict writer is of any use at all.

On Sat, Apr 26, 2014 at 11:28 AM, Ross Paterson
On Sat, Apr 26, 2014 at 09:16:57AM +0300, Roman Cheplyaka wrote:
* Ross Paterson
[2014-04-26 01:21:09+0100] Instead of EitherT, the next version will deprecate ErrorT in favour of a transformer ExceptT with base monad Except. The idea is to have analogous transformers and monads
ExceptT : Except : Either WriterT : Writer : (,) ReaderT : Reader : (->)
Great! When do you plan to make a release?
Let's say Wednesday, if no-one notices a major problem.
Pre-release docs are here:
http://code.haskell.org/~ross/transformers/dist/doc/html/transformers/
The docs for Control.Monad.Trans.Writer.Strict say:
Although the output is built strictly, it is not possible to achieve linear space behaviour with this transformer: for that, use Control.Monad.Trans.State.Strict instead.
I think it should be "constant", not "linear".
Indeed -- thanks for catching that. I wonder whether the strict writer is of any use at all.
I think it's worth resurrecting Gabriel's proposed modification to have the strict writer transformer exposed as an abstract type, built on top of StateT (or using the same implementation as StateT). I've been bitten by the laziness of strict Writer in the past, and thanks to Gabriel's email, I knew how to solve the problem. But I think many people will be misled by the name, documentation improvements notwithstanding. *If* it's exposed as an abstract type, I'd also like to propose that a .Internal module be available for exposing the constructor, as some libraries will have legitimate need of looking at the constructor. Michael

On Sat, Apr 26, 2014 at 09:12:12PM +0300, Michael Snoyman wrote:
I think it's worth resurrecting Gabriel's proposed modification to have the strict writer transformer exposed as an abstract type, built on top of StateT (or using the same implementation as StateT). I've been bitten by the laziness of strict Writer in the past, and thanks to Gabriel's email, I knew how to solve the problem. But I think many people will be misled by the name, documentation improvements notwithstanding.
Indeed it's a trap. But an abstract type would be less transparent than the other transformers, and would be incompatible with the lazy WriterT in subtle ways. How about just deprecating strict WriterT in favour of strict StateT?

* Ross Paterson
On Sat, Apr 26, 2014 at 09:12:12PM +0300, Michael Snoyman wrote:
I think it's worth resurrecting Gabriel's proposed modification to have the strict writer transformer exposed as an abstract type, built on top of StateT (or using the same implementation as StateT). I've been bitten by the laziness of strict Writer in the past, and thanks to Gabriel's email, I knew how to solve the problem. But I think many people will be misled by the name, documentation improvements notwithstanding.
Indeed it's a trap. But an abstract type would be less transparent than the other transformers, and would be incompatible with the lazy WriterT in subtle ways.
How about just deprecating strict WriterT in favour of strict StateT?
I don't understand the issue here. Why does it have to be abstract or based on StateT? We could simply make a new module with the same WriterT type and the instance instance (Monoid w, Monad m) => Monad (WriterT w m) where m >>= k = WriterT $ do (a, w) <- runWriterT m (b, w') <- runWriterT (k a) let w'' = w `mappend` w' w'' `seq` return (b, w'') I'll leave it up to others to bikeshed the name of such a module (or maybe we should simply replace the current Writer.Strict?) Roman

On Sat, Apr 26, 2014 at 11:29:01PM +0300, Roman Cheplyaka wrote:
I don't understand the issue here. Why does it have to be abstract or based on StateT?
We could simply make a new module with the same WriterT type and the instance
instance (Monoid w, Monad m) => Monad (WriterT w m) where m >>= k = WriterT $ do (a, w) <- runWriterT m (b, w') <- runWriterT (k a) let w'' = w `mappend` w' w'' `seq` return (b, w'')
See Gabriel's analysis: http://www.haskell.org/pipermail/libraries/2013-March/019528.html The above is version #2 there.

While I think that we should follow PHP's good example and call such a potential new module Control.Monad.Trans.Writer.Really_Strict, would there be actual drawbacks for changing Writer.Strict to Gabriel's suggestions? On Sun 27 Apr 2014 00:51:40 BST, Ross Paterson wrote:
On Sat, Apr 26, 2014 at 11:29:01PM +0300, Roman Cheplyaka wrote:
I don't understand the issue here. Why does it have to be abstract or based on StateT?
We could simply make a new module with the same WriterT type and the instance
instance (Monoid w, Monad m) => Monad (WriterT w m) where m >>= k = WriterT $ do (a, w) <- runWriterT m (b, w') <- runWriterT (k a) let w'' = w `mappend` w' w'' `seq` return (b, w'')
See Gabriel's analysis:
http://www.haskell.org/pipermail/libraries/2013-March/019528.html
The above is version #2 there. _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

* Ross Paterson
On Sat, Apr 26, 2014 at 11:29:01PM +0300, Roman Cheplyaka wrote:
I don't understand the issue here. Why does it have to be abstract or based on StateT?
We could simply make a new module with the same WriterT type and the instance
instance (Monoid w, Monad m) => Monad (WriterT w m) where m >>= k = WriterT $ do (a, w) <- runWriterT m (b, w') <- runWriterT (k a) let w'' = w `mappend` w' w'' `seq` return (b, w'')
See Gabriel's analysis:
http://www.haskell.org/pipermail/libraries/2013-March/019528.html
The above is version #2 there.
Very illuminating, thanks. Roman

On Sat, Apr 26, 2014 at 9:57 PM, Ross Paterson
I think it's worth resurrecting Gabriel's proposed modification to have
On Sat, Apr 26, 2014 at 09:12:12PM +0300, Michael Snoyman wrote: the
strict writer transformer exposed as an abstract type, built on top of StateT (or using the same implementation as StateT). I've been bitten by the laziness of strict Writer in the past, and thanks to Gabriel's email, I knew how to solve the problem. But I think many people will be misled by the name, documentation improvements notwithstanding.
Indeed it's a trap. But an abstract type would be less transparent than the other transformers, and would be incompatible with the lazy WriterT in subtle ways.
How about just deprecating strict WriterT in favour of strict StateT?
would be incompatible with the lazy WriterT in subtle ways
That would be troubling, but I'm not sure in which ways it's incompatible. Do you have any examples? The advantage of having WriterT implemented in terms of strict StateT is that many people will automatically get the fix when upgrading to transformers 0.4. Also, the writer API itself is very convenient for many common use cases, so it would be nice if there was a version available that didn't leak memory. Michael

Note: Lazy.WriterT can be used in ways that bottom out with
Strict.WriterTor the even stricter
StateT writer variant.
*e.g.*
snd $ runWriter $ fix (tell [1] >>)
-Edward
On Sun, Apr 27, 2014 at 3:47 AM, Michael Snoyman
On Sat, Apr 26, 2014 at 9:57 PM, Ross Paterson
wrote: I think it's worth resurrecting Gabriel's proposed modification to have
On Sat, Apr 26, 2014 at 09:12:12PM +0300, Michael Snoyman wrote: the
strict writer transformer exposed as an abstract type, built on top of StateT (or using the same implementation as StateT). I've been bitten by the laziness of strict Writer in the past, and thanks to Gabriel's email, I knew how to solve the problem. But I think many people will be misled by the name, documentation improvements notwithstanding.
Indeed it's a trap. But an abstract type would be less transparent than the other transformers, and would be incompatible with the lazy WriterT in subtle ways.
How about just deprecating strict WriterT in favour of strict StateT?
would be incompatible with the lazy WriterT in subtle ways
That would be troubling, but I'm not sure in which ways it's incompatible. Do you have any examples?
The advantage of having WriterT implemented in terms of strict StateT is that many people will automatically get the fix when upgrading to transformers 0.4. Also, the writer API itself is very convenient for many common use cases, so it would be nice if there was a version available that didn't leak memory.
Michael
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

To be clear, I'm not at all proposing changing the lazy WriterT, I'm only
talking about expressing the strict WriterT in terms of the strict StateT.
On Sun, Apr 27, 2014 at 5:19 PM, Edward Kmett
Note: Lazy.WriterT can be used in ways that bottom out with Strict.WriterTor the even stricter StateT writer variant.
*e.g.*
snd $ runWriter $ fix (tell [1] >>)
-Edward
On Sun, Apr 27, 2014 at 3:47 AM, Michael Snoyman
wrote: On Sat, Apr 26, 2014 at 9:57 PM, Ross Paterson
wrote: On Sat, Apr 26, 2014 at 09:12:12PM +0300, Michael Snoyman wrote:
I think it's worth resurrecting Gabriel's proposed modification to have the strict writer transformer exposed as an abstract type, built on top of StateT (or using the same implementation as StateT). I've been bitten by the laziness of strict Writer in the past, and thanks to Gabriel's email, I knew how to solve the problem. But I think many people will be misled by the name, documentation improvements notwithstanding.
Indeed it's a trap. But an abstract type would be less transparent than the other transformers, and would be incompatible with the lazy WriterT in subtle ways.
How about just deprecating strict WriterT in favour of strict StateT?
would be incompatible with the lazy WriterT in subtle ways
That would be troubling, but I'm not sure in which ways it's incompatible. Do you have any examples?
The advantage of having WriterT implemented in terms of strict StateT is that many people will automatically get the fix when upgrading to transformers 0.4. Also, the writer API itself is very convenient for many common use cases, so it would be nice if there was a version available that didn't leak memory.
Michael
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

Come to think of it I'm not currently aware of anything that works
correctly with strict writer that doesn't work with the strict state
encoding.
-Edward
On Sun, Apr 27, 2014 at 10:51 AM, Michael Snoyman
To be clear, I'm not at all proposing changing the lazy WriterT, I'm only talking about expressing the strict WriterT in terms of the strict StateT.
On Sun, Apr 27, 2014 at 5:19 PM, Edward Kmett
wrote: Note: Lazy.WriterT can be used in ways that bottom out with Strict.WriterT or the even stricter StateT writer variant.
*e.g.*
snd $ runWriter $ fix (tell [1] >>)
-Edward
On Sun, Apr 27, 2014 at 3:47 AM, Michael Snoyman
wrote: On Sat, Apr 26, 2014 at 9:57 PM, Ross Paterson
wrote: On Sat, Apr 26, 2014 at 09:12:12PM +0300, Michael Snoyman wrote:
I think it's worth resurrecting Gabriel's proposed modification to have the strict writer transformer exposed as an abstract type, built on top of StateT (or using the same implementation as StateT). I've been bitten by the laziness of strict Writer in the past, and thanks to Gabriel's email, I knew how to solve the problem. But I think many people will be misled by the name, documentation improvements notwithstanding.
Indeed it's a trap. But an abstract type would be less transparent than the other transformers, and would be incompatible with the lazy WriterT in subtle ways.
How about just deprecating strict WriterT in favour of strict StateT?
would be incompatible with the lazy WriterT in subtle ways
That would be troubling, but I'm not sure in which ways it's incompatible. Do you have any examples?
The advantage of having WriterT implemented in terms of strict StateT is that many people will automatically get the fix when upgrading to transformers 0.4. Also, the writer API itself is very convenient for many common use cases, so it would be nice if there was a version available that didn't leak memory.
Michael
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On Sun, Apr 27, 2014 at 10:47:56AM +0300, Michael Snoyman wrote:
On Sat, Apr 26, 2014 at 9:57 PM, Ross Paterson
wrote: would be incompatible with the lazy WriterT in subtle ways
That would be troubling, but I'm not sure in which ways it's incompatible. Do you have any examples?
The Applicative and Alternative instances would have different contexts, and there would be no instances for Foldable, Traversable, Eq, Ord, Read or Show.
The advantage of having WriterT implemented in terms of strict StateT is that many people will automatically get the fix when upgrading to transformers 0.4. Also, the writer API itself is very convenient for many common use cases, so it would be nice if there was a version available that didn't leak memory.
Invisibly increasing strictness cuts both ways: some people get space savings, while others get non-termination. (Although one might say they're not using it properly, that seems a harsh punishment.) But I'm more concerned about the complication. Currently the transformers are transparent, and people can think about the type structure of the monad they're building. This very transformer is already there; it seems simpler to direct people to it instead of having another copy. The API point is an issue, though.

On Mon, Apr 28, 2014 at 4:15 PM, Ross Paterson
On Sun, Apr 27, 2014 at 10:47:56AM +0300, Michael Snoyman wrote:
On Sat, Apr 26, 2014 at 9:57 PM, Ross Paterson
wrote: would be incompatible with the lazy WriterT in subtle ways
That would be troubling, but I'm not sure in which ways it's incompatible. Do you have any examples?
The Applicative and Alternative instances would have different contexts, and there would be no instances for Foldable, Traversable, Eq, Ord, Read or Show.
If we have deprecation of the module in its entirety on the table, I think it's acceptable to consider dropping some instances. However, I don't see Eq, Ord, Read, or Show instances for strict WriterT in transformers 0.3. Applicative seems like it should be identical in behavior to what we have right now. I'm not completely certain, but it seems the same is true for Alternative.
The advantage of having WriterT implemented in terms of strict StateT is that many people will automatically get the fix when upgrading to transformers 0.4. Also, the writer API itself is very convenient for many common use cases, so it would be nice if there was a version available that didn't leak memory.
Invisibly increasing strictness cuts both ways: some people get space savings, while others get non-termination. (Although one might say they're not using it properly, that seems a harsh punishment.) But I'm more concerned about the complication. Currently the transformers are transparent, and people can think about the type structure of the monad they're building. This very transformer is already there; it seems simpler to direct people to it instead of having another copy. The API point is an issue, though.
Here's the question I'd ask, which I honestly don't know the answer to. We have three proposed WriterT implementations: lazy, current-strict, and state-strict. We have two conflicting desires: program termination and space savings. We know there are cases where lazy allows termination where state-strict does not. We know there are cases where state-strict allows space savings where neither lazy nor current-strict do. The question is: are there cases where current-strict: 1. Gives space savings that lazy does not? 2. Gives termination where state-strict does not? I *think* the answers to these questions are "no" and "yes", meaning that current-strict in its current form can *always* be replaced by lazy, without losing anything. If that's the case, I'd say this is a very simple transition in 0.4. Note that we've been discussing all of this in terms of WriterT, but the same exact discussion should apply to RWST. Michael

On Mon, Apr 28, 2014 at 07:00:25PM +0300, Michael Snoyman wrote:
On Mon, Apr 28, 2014 at 4:15 PM, Ross Paterson
wrote: The Applicative and Alternative instances would have different contexts, and there would be no instances for Foldable, Traversable, Eq, Ord, Read or Show. If we have deprecation of the module in its entirety on the table, I think it's acceptable to consider dropping some instances. However, I don't see Eq, Ord, Read, or Show instances for strict WriterT in transformers 0.3. Applicative seems like it should be identical in behavior to what we have right now. I'm not completely certain, but it seems the same is true for Alternative.
I was more concerned with consistency across the interface in the new version. Here the Applicative and Alternative instances for the state-based WriterT would have Monad constraints, while the lazy one just had Applicative constraints, and the lazy transformer would have Eq, Ord, Read, or Show instances while the strict one wouldn't.
Here's the question I'd ask, which I honestly don't know the answer to. We have three proposed WriterT implementations: lazy, current-strict, and state-strict. We have two conflicting desires: program termination and space savings. We know there are cases where lazy allows termination where state-strict does not. We know there are cases where state-strict allows space savings where neither lazy nor current-strict do.
The question is: are there cases where current-strict:
1. Gives space savings that lazy does not? 2. Gives termination where state-strict does not?
I *think* the answers to these questions are "no" and "yes", meaning that current-strict in its current form can *always* be replaced by lazy, without losing anything. If that's the case, I'd say this is a very simple transition in 0.4.
Of course strictness sometimes means more space, but you may be right on the termination issue.

As a straw man, if we really don't export the constructor and implement the
writerT API abstractly you can actually can implement Show/Read/Ord/Eq
correctly.
Under the assumption that it only uses the state as a writer context: we
could safely pass it the mempty state for display purposes to capture the
information present.
instance (Show1 m, Show e, Monoid e) => Show1 (WriterT e m) where
showsPrec1 d (WriterT f) = showParen (d > 10) $
showString "writerT " . showsPrec1 11 (f mempty)
instance (Eq1 m, Eq e, Monoid e) => Eq1 (WriterT e m) where
eq1 (WriterT f) (WriterT g) = f mempty == g mempty
...
writerT :: (Monad m, Monoid e) => m (e, a) -> WriterT e m a
writerT mea = WriterT $ \s -> do
(e, a) <- mea
return $! (s <> e, a)
runWriterT :: Monoid e => WriterT e m a -> m (e, a)
runWriterT (WriterT f) = f mempty
...
On Tue, Apr 29, 2014 at 8:46 PM, Ross Paterson
On Mon, Apr 28, 2014 at 07:00:25PM +0300, Michael Snoyman wrote:
On Mon, Apr 28, 2014 at 4:15 PM, Ross Paterson
wrote: The Applicative and Alternative instances would have different contexts, and there would be no instances for Foldable, Traversable, Eq, Ord, Read or Show. If we have deprecation of the module in its entirety on the table, I think it's acceptable to consider dropping some instances. However, I don't see Eq, Ord, Read, or Show instances for strict WriterT in transformers 0.3. Applicative seems like it should be identical in behavior to what we have right now. I'm not completely certain, but it seems the same is true for Alternative.
I was more concerned with consistency across the interface in the new version. Here the Applicative and Alternative instances for the state-based WriterT would have Monad constraints, while the lazy one just had Applicative constraints, and the lazy transformer would have Eq, Ord, Read, or Show instances while the strict one wouldn't.
Here's the question I'd ask, which I honestly don't know the answer to. We have three proposed WriterT implementations: lazy, current-strict, and state-strict. We have two conflicting desires: program termination and space savings. We know there are cases where lazy allows termination where state-strict does not. We know there are cases where state-strict allows space savings where neither lazy nor current-strict do.
The question is: are there cases where current-strict:
1. Gives space savings that lazy does not? 2. Gives termination where state-strict does not?
I *think* the answers to these questions are "no" and "yes", meaning that current-strict in its current form can *always* be replaced by lazy, without losing anything. If that's the case, I'd say this is a very simple transition in 0.4.
Of course strictness sometimes means more space, but you may be right on the termination issue. _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On Wed, Apr 30, 2014 at 01:11:19AM -0400, Edward Kmett wrote:
As a straw man, if we really don't export the constructor and implement the writerT API abstractly you can actually can implement Show/Read/Ord/Eq correctly.
Under the assumption that it only uses the state as a writer context: we could safely pass it the mempty state for display purposes to capture the information present.
That's neat (the power of abstraction), but people might be surprised by the performance of things like let m = enormous computation in m == m There's a similar issue with the Applicative instance, and indeed any situation where the lazy instance would give a shared value while the state-based one wouldn't. There's a strong argument for transparent types in transformers, which many people already find complex.

On Sat, Apr 26, 2014 at 09:28:47AM +0100, Ross Paterson wrote:
On Sat, Apr 26, 2014 at 09:16:57AM +0300, Roman Cheplyaka wrote:
* Ross Paterson
[2014-04-26 01:21:09+0100] Instead of EitherT, the next version will deprecate ErrorT in favour of a transformer ExceptT with base monad Except. The idea is to have analogous transformers and monads
ExceptT : Except : Either WriterT : Writer : (,) ReaderT : Reader : (->)
Great! When do you plan to make a release?
Let's say Wednesday, if no-one notices a major problem.
I'll put it off a couple of days, as there's currently discussion of two issues: - strict writer - definition of (<|>)/mplus for ExceptT

On 14-04-25 08:21 PM, Ross Paterson wrote:
Other changes are:
* Added infixr 9 `Compose` to match (.) * Added Eq, Ord, Read and Show instances where possible * Replaced record syntax for newtypes with separate inverse functions * Added delimited continuation functions to ContT * Added instance Alternative IO to ErrorT
Pre-release docs are here:
http://code.haskell.org/~ross/transformers/dist/doc/html/transformers/
Did the Coproduct proposal then get rejected? :( http://www.haskell.org/pipermail/libraries/2012-December/019099.html

On Mon, Apr 28, 2014 at 05:21:29PM -0400, Mario Blažević wrote:
Did the Coproduct proposal then get rejected? :(
http://www.haskell.org/pipermail/libraries/2012-December/019099.html
I've put it in, though it's not a monad or applicative functor transformer.

Hello, Ross I discovered mplus of ExceptT doesn't call mappend to accumulate error states which is different from origitnal EitherT like below. I suppose this EitherT semantics is more useful than fixed adoption of last error state. (For example, Last Monoid is pre-defined in base) ExceptT
instance (Monad m, Monoid e) => MonadPlus (ExceptT e m) where mzero = ExceptT $ return (Left mempty) ExceptT m `mplus` ExceptT n = ExceptT $ do a <- m case a of Left _ -> n -- throw left error away Right x -> return (Right x)
EitherT
instance (Monad m, Monoid e) => Alternative (EitherT e m) where EitherT m <|> EitherT n = EitherT $ m >>= \a -> case a of Left l -> liftM (\b -> case b of Left l' -> Left (mappend l l') -- mappend error states Right r -> Right r) n Right r -> return (Right r)
empty = EitherT $ return (Left mempty)
From: R.Paterson at city.ac.uk (Ross Paterson) Subject: Proposal: merge either into transformers Date: Sat, 26 Apr 2014 01:21:09 +0100
Instead of EitherT, the next version will deprecate ErrorT in favour of a transformer ExceptT with base monad Except. The idea is to have analogous transformers and monads
ExceptT : Except : Either WriterT : Writer : (,) ReaderT : Reader : (->)
Other changes are:
* Added infixr 9 `Compose` to match (.) * Added Eq, Ord, Read and Show instances where possible * Replaced record syntax for newtypes with separate inverse functions * Added delimited continuation functions to ContT * Added instance Alternative IO to ErrorT
Pre-release docs are here:
http://code.haskell.org/~ross/transformers/dist/doc/html/transformers/
-- Kei Hibino ex8k.hibino at gmail.com https://github.com/khibino/

On Wed, Apr 30, 2014 at 06:00:50PM +0900, Kei Hibino wrote:
I discovered mplus of ExceptT doesn't call mappend to accumulate error states which is different from origitnal EitherT like below. I suppose this EitherT semantics is more useful than fixed adoption of last error state. (For example, Last Monoid is pre-defined in base)
ExceptT
instance (Monad m, Monoid e) => MonadPlus (ExceptT e m) where mzero = ExceptT $ return (Left mempty) ExceptT m `mplus` ExceptT n = ExceptT $ do a <- m case a of Left _ -> n -- throw left error away Right x -> return (Right x)
EitherT
instance (Monad m, Monoid e) => Alternative (EitherT e m) where EitherT m <|> EitherT n = EitherT $ m >>= \a -> case a of Left l -> liftM (\b -> case b of Left l' -> Left (mappend l l') -- mappend error states Right r -> Right r) n Right r -> return (Right r)
empty = EitherT $ return (Left mempty)
Yes, the ExceptT instance is similar to the ErrorT one. The accumulating one in EitherT is more flexible (and consistent with using mempty in the mzero case), but it's also more expensive than the tail call in the ErrorT version. What do others think?

I personally would rather pay than lose information.
On Wed, Apr 30, 2014 at 6:24 AM, Ross Paterson
On Wed, Apr 30, 2014 at 06:00:50PM +0900, Kei Hibino wrote:
I discovered mplus of ExceptT doesn't call mappend to accumulate error states which is different from origitnal EitherT like below. I suppose this EitherT semantics is more useful than fixed adoption of last error state. (For example, Last Monoid is pre-defined in base)
ExceptT
instance (Monad m, Monoid e) => MonadPlus (ExceptT e m) where mzero = ExceptT $ return (Left mempty) ExceptT m `mplus` ExceptT n = ExceptT $ do a <- m case a of Left _ -> n -- throw left error away Right x -> return (Right x)
EitherT
instance (Monad m, Monoid e) => Alternative (EitherT e m) where EitherT m <|> EitherT n = EitherT $ m >>= \a -> case a of Left l -> liftM (\b -> case b of Left l' -> Left (mappend l l') -- mappend error states Right r -> Right r) n Right r -> return (Right r)
empty = EitherT $ return (Left mempty)
Yes, the ExceptT instance is similar to the ErrorT one. The accumulating one in EitherT is more flexible (and consistent with using mempty in the mzero case), but it's also more expensive than the tail call in the ErrorT version.
What do others think? _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

With that, I'll finish up the mtl changes over this weekend. I'm on flights
for the next 24 hours though.
-Edward
On Fri, May 2, 2014 at 12:38 PM, Ross Paterson
On Wed, Apr 30, 2014 at 09:31:37AM -0400, Edward Kmett wrote:
I personally would rather pay than lose information.
OK, it seems neater too, so I've done that. _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

Vincent Hanquez wrote:
On 2012-12-07 09:44, Roman Cheplyaka wrote:
I propose to add the sole module of the 'either' package[1], Control.Monad.Trans.Either, to the transformers package.
It provides EitherT, a very basic and fundamental data type. The difference between EitherT and ErrorT is that the latter has an Error constraint, which is used to imlement 'fail'.
Note that 'either' depends on the 'semigroupoids' and 'semigroup' packages to provide appropriate instances. The proposal is not to add those instances to 'transformers' to avoid additional dependencies. The instances can then be left in the 'either' package or moved to the 'semigroupoids' and 'semigroup' packages respectively. ('semigroupoids' already depends on 'transformers', while 'semigroups' does not).
Compared to the 'either' package, Show, Read, Eq and Ord instances will be dropped to keep the code Haskell2010 (those instances require FlexibleInstances, FlexibleContexts, and UndecidableInstances).
The patch is attached. [*]
[*] against transformers-0.3.0.0, because the darcs version is not buildable (Control/Monad/Signatures.hs is not in the repository).
[Sorry to revive this 1 yr 1/2 thread, but I was looking at the reason why we don't have eitherT is a more canonical place like transformers, and ended up here ...]
Is there a reason why this thread ran out of steam ? It not totally obvious from the answers what was missing to move forward. It seems like there's general agreement that EitherT is a good addition, did this proposal got forgotten ? Is there a way to revive this proposal ?
So now its me reviving a 2 1/2 year old response to a 6 year old thread. I came here exactly the same way as Vincent, wanting to a couple of new combinators added to the either library, noticing that there was talk of moving Control.Monad.Trans.Either to transformers or transformers-compat and then it seemed to loose steam. Any clues as to where we're at with this? Erik -- ---------------------------------------------------------------------- Erik de Castro Lopo http://www.mega-nerd.com/

Perhaps ExceptT is what you're looking for? Check out the
'Control.Monad.Trans.Except' module in 'transformers'.
On Mon, Jan 2, 2017 at 4:24 AM, Erik de Castro Lopo
Vincent Hanquez wrote:
On 2012-12-07 09:44, Roman Cheplyaka wrote:
I propose to add the sole module of the 'either' package[1], Control.Monad.Trans.Either, to the transformers package.
It provides EitherT, a very basic and fundamental data type. The difference between EitherT and ErrorT is that the latter has an Error constraint, which is used to imlement 'fail'.
Note that 'either' depends on the 'semigroupoids' and 'semigroup' packages to provide appropriate instances. The proposal is not to add those instances to 'transformers' to avoid additional dependencies. The instances can then be left in the 'either' package or moved to the 'semigroupoids' and 'semigroup' packages respectively. ('semigroupoids' already depends on 'transformers', while 'semigroups' does not).
Compared to the 'either' package, Show, Read, Eq and Ord instances will be dropped to keep the code Haskell2010 (those instances require FlexibleInstances, FlexibleContexts, and UndecidableInstances).
The patch is attached. [*]
[*] against transformers-0.3.0.0, because the darcs version is not buildable (Control/Monad/Signatures.hs is not in the repository).
[Sorry to revive this 1 yr 1/2 thread, but I was looking at the reason why we don't have eitherT is a more canonical place like transformers, and ended up here ...]
Is there a reason why this thread ran out of steam ? It not totally obvious from the answers what was missing to move forward. It seems like there's general agreement that EitherT is a good addition, did this proposal got forgotten ? Is there a way to revive this proposal ?
So now its me reviving a 2 1/2 year old response to a 6 year old thread.
I came here exactly the same way as Vincent, wanting to a couple of new combinators added to the either library, noticing that there was talk of moving Control.Monad.Trans.Either to transformers or transformers-compat and then it seemed to loose steam.
Any clues as to where we're at with this?
Erik -- ---------------------------------------------------------------------- Erik de Castro Lopo http://www.mega-nerd.com/ _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Indeed. A proper "EitherT" was added, but due to bikeshedding turned into
ExceptT in the process complicating the migration story a fair bit. To get
a version of ExceptT for older transformers versions you can use
transformers-compat, so there is at least some migration story. =/
The either package will have the EitherT component deprecated eventually,
but should continue to exist for the combinators.
-Edward
On Sun, Jan 1, 2017 at 9:16 PM, Index Int
Perhaps ExceptT is what you're looking for? Check out the 'Control.Monad.Trans.Except' module in 'transformers'.
Vincent Hanquez wrote:
On 2012-12-07 09:44, Roman Cheplyaka wrote:
I propose to add the sole module of the 'either' package[1], Control.Monad.Trans.Either, to the transformers package.
It provides EitherT, a very basic and fundamental data type. The difference between EitherT and ErrorT is that the latter has an Error constraint, which is used to imlement 'fail'.
Note that 'either' depends on the 'semigroupoids' and 'semigroup' packages to provide appropriate instances. The proposal is not to add those instances to 'transformers' to avoid additional dependencies. The instances can then be left in the 'either' package or moved to the 'semigroupoids' and 'semigroup' packages respectively. ('semigroupoids' already depends on 'transformers', while 'semigroups' does not).
Compared to the 'either' package, Show, Read, Eq and Ord instances will be dropped to keep the code Haskell2010 (those instances require FlexibleInstances, FlexibleContexts, and UndecidableInstances).
The patch is attached. [*]
[*] against transformers-0.3.0.0, because the darcs version is not buildable (Control/Monad/Signatures.hs is not in the repository).
[Sorry to revive this 1 yr 1/2 thread, but I was looking at the reason why we don't have eitherT is a more canonical place like transformers, and ended up here ...]
Is there a reason why this thread ran out of steam ? It not totally obvious from the answers what was missing to move forward. It seems like there's general agreement that EitherT is a good addition, did this proposal got forgotten ? Is there a way to revive this
On Mon, Jan 2, 2017 at 4:24 AM, Erik de Castro Lopo
wrote: proposal ? So now its me reviving a 2 1/2 year old response to a 6 year old thread.
I came here exactly the same way as Vincent, wanting to a couple of new combinators added to the either library, noticing that there was talk of moving Control.Monad.Trans.Either to transformers or
transformers-compat
and then it seemed to loose steam.
Any clues as to where we're at with this?
Erik -- ---------------------------------------------------------------------- Erik de Castro Lopo http://www.mega-nerd.com/ _______________________________________________ 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 Kmett wrote:
Indeed. A proper "EitherT" was added, but due to bikeshedding turned into ExceptT in the process complicating the migration story a fair bit. To get a version of ExceptT for older transformers versions you can use transformers-compat, so there is at least some migration story. =/
Thanks Ed. I'm really only interested in GHC 7.10 and later, but there are a number of combinators in Control.Monad.Trans.Either that seem to be missing from Control.Monad.Trans.Except and in my day job we have a extended version of Control.Monad.Trans.Either that has yet more combinators that I miss whenever I write code outside the work environment. Combinators in C.M.T.Either but not in C.M.T.Except: bimapEitherT :: Functor m => (e -> f) -> (a -> b) -> EitherT e m a -> EitherT f m b -- really just an alias for EitherT constructor hoistEither :: Monad m => Either e a -> EitherT e m a Combinators which I am used to using at work include: firstEitherT :: Functor m => (x -> y) -> EitherT x m a -> EitherT y m a secondEitherT :: Functor m => (a -> b) -> EitherT e m a -> EitherT e m b tryEitherT :: (Functor m, MonadCatch m, Exception e) => (e -> x) -> m a -> EitherT x m a There are probably others which I can't remember just now. Whats the right place for these, the C.M.T.Except or somewhere else? I'd prefer not to have to carry them from project to project. Erik -- ---------------------------------------------------------------------- Erik de Castro Lopo http://www.mega-nerd.com/

A couple of these are in transformers already.
Combinators which I am used to using at work include:
firstEitherT :: Functor m => (x -> y) -> EitherT x m a -> EitherT y m a
https://hackage.haskell.org/package/transformers-0.5.2.0/docs/Control-Monad-...
secondEitherT :: Functor m => (a -> b) -> EitherT e m a -> EitherT e m b
This is just fmap -- Chris Wong (https://lambda.xyz) "I had not the vaguest idea what this meant and when I could not remember the words, my tutor threw the book at my head, which did not stimulate my intellect in any way." -- Bertrand Russell

Chris Wong wrote:
secondEitherT :: Functor m => (a -> b) -> EitherT e m a -> EitherT e m b
This is just fmap
Doh! Yes, yes it is. Erik -- ---------------------------------------------------------------------- Erik de Castro Lopo http://www.mega-nerd.com/

On Mon, Jan 2, 2017 at 2:14 AM, Erik de Castro Lopo
Combinators in C.M.T.Either but not in C.M.T.Except:
bimapEitherT :: Functor m => (e -> f) -> (a -> b) -> EitherT e m a -> EitherT f m b
It's not a very pretty substitute, but note that bimapEitherT f g = mapExceptT (fmap (bimap f g))

I sympathize. If you feel the need for those combinators, you can talk to
Ross to try to get him to add them to the library. (Well, secondEitherT is
already fmap, of course.) When the ExceptT API was crafted, it pretty much
tried to follow the API of the rest of transformers, and didn't really take
any of the extra combinators we had in the either package into account. =/
You might have a hard time getting the last one adopted, though, due to the
dependency on exceptions taking the API into "non-standard" territory.
Unfortunately, even if Ross adds them, I have no way to supply them in
transformers-compat when used with middle versions of transformers that
have ExceptT, but not those combinators, so the compatibility hack I offer
will suffer a bit.
-Edward
On Mon, Jan 2, 2017 at 2:14 AM, Erik de Castro Lopo
Edward Kmett wrote:
Indeed. A proper "EitherT" was added, but due to bikeshedding turned into ExceptT in the process complicating the migration story a fair bit. To get a version of ExceptT for older transformers versions you can use transformers-compat, so there is at least some migration story. =/
Thanks Ed.
I'm really only interested in GHC 7.10 and later, but there are a number of combinators in Control.Monad.Trans.Either that seem to be missing from Control.Monad.Trans.Except and in my day job we have a extended version of Control.Monad.Trans.Either that has yet more combinators that I miss whenever I write code outside the work environment.
Combinators in C.M.T.Either but not in C.M.T.Except:
bimapEitherT :: Functor m => (e -> f) -> (a -> b) -> EitherT e m a -> EitherT f m b
-- really just an alias for EitherT constructor hoistEither :: Monad m => Either e a -> EitherT e m a
Combinators which I am used to using at work include:
firstEitherT :: Functor m => (x -> y) -> EitherT x m a -> EitherT y m a
secondEitherT :: Functor m => (a -> b) -> EitherT e m a -> EitherT e m b
tryEitherT :: (Functor m, MonadCatch m, Exception e) => (e -> x) -> m a -> EitherT x m a
There are probably others which I can't remember just now.
Whats the right place for these, the C.M.T.Except or somewhere else? I'd prefer not to have to carry them from project to project.
Erik -- ---------------------------------------------------------------------- Erik de Castro Lopo http://www.mega-nerd.com/ _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Edward Kmett wrote:
I sympathize. If you feel the need for those combinators, you can talk to Ross to try to get him to add them to the library.
Where/how is transformers even maintained. The github mirror at: https://github.com/ghc/packages-transformers offers no clue.
(Well, secondEitherT is already fmap, of course.)
Yes, still a little embarrased about that :).
When the ExceptT API was crafted, it pretty much tried to follow the API of the rest of transformers, and didn't really take any of the extra combinators we had in the either package into account. =/
That was unfortunate.
You might have a hard time getting the last one adopted, though, due to the dependency on exceptions taking the API into "non-standard" territory.
What is the problem here, the `Exception` constraint, the `MonadCatch` constraint or both?
Unfortunately, even if Ross adds them, I have no way to supply them in transformers-compat when used with middle versions of transformers that have ExceptT, but not those combinators, so the compatibility hack I offer will suffer a bit.
Can't be done even with CPP? Erik -- ---------------------------------------------------------------------- Erik de Castro Lopo http://www.mega-nerd.com/

On Mon, Jan 2, 2017 at 1:58 PM, Erik de Castro Lopo
Edward Kmett wrote:
I sympathize. If you feel the need for those combinators, you can talk to Ross to try to get him to add them to the library.
Where/how is transformers even maintained. The github mirror at:
https://github.com/ghc/packages-transformers
offers no clue.
It is maintained on darcs: http://hub.darcs.net/ross/transformers
(Well, secondEitherT is already fmap, of course.)
Yes, still a little embarrased about that :).
=)
When the ExceptT API was crafted, it pretty much tried to follow the API of the rest of transformers, and didn't really take any of the extra combinators we had in the either package into account. =/
That was unfortunate.
I made some noises to that effect at the time. *shrug*
You might have a hard time getting the last one adopted, though, due to the
dependency on exceptions taking the API into "non-standard" territory.
What is the problem here, the `Exception` constraint, the `MonadCatch` constraint or both?
Both. Control.Exception needs a bunch of extensions to make sense taking it outside of Haskell 2010. transformers has as much as possible tried to stick to a standard language.
Unfortunately, even if Ross adds them, I have no way to supply them in transformers-compat when used with middle versions of transformers that have ExceptT, but not those combinators, so the compatibility hack I offer will suffer a bit.
Can't be done even with CPP?
Unfortunately not. Once you get to a transformers version that exports that module, then the module then is supplied by transformers, not transformers-compat. If you can get the extra combinators into transformers, I might be able to offer a C.M.T.E.Compat module that you could import along with C.M.T.E to get the new API across those intermediate versions, but I've yet to adopt this practice for the other transformers modules. If someone wanted to toss a patch at transformers-compat that added .Compat modules with the changes to the transformers API over time, (like adding reader, state, writer combinators), I'd probably take the patch, but I don't have a definitive list of what they are and the design would involve some compromises. -Edward
Erik -- ---------------------------------------------------------------------- Erik de Castro Lopo http://www.mega-nerd.com/ _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Edward Kmett wrote:
If you can get the extra combinators into transformers, I might be able to offer a C.M.T.E.Compat module that you could import along with C.M.T.E to get the new API across those intermediate versions, but I've yet to adopt this practice for the other transformers modules. If someone wanted to toss a patch at transformers-compat that added .Compat modules with the changes to the transformers API over time, (like adding reader, state, writer combinators), I'd probably take the patch, but I don't have a definitive list of what they are and the design would involve some compromises.
I found another solution. Gabriel Gonzalez's errors package already had much of what I needed and he accepted a PR today to add: handleExceptT :: (Exception e, Functor m, MonadCatch m) => (e -> x) -> m a -> ExceptT x m a handleExceptT handler = bimapExceptT handler id . ExceptT . try The names Gabriel uses are slightly different from what I'm used to but the types are as expected :). Cheers, Erik -- ---------------------------------------------------------------------- Erik de Castro Lopo http://www.mega-nerd.com/

On Tue, 3 Jan 2017, Erik de Castro Lopo wrote:
Edward Kmett wrote:
If you can get the extra combinators into transformers, I might be able to offer a C.M.T.E.Compat module that you could import along with C.M.T.E to get the new API across those intermediate versions, but I've yet to adopt this practice for the other transformers modules. If someone wanted to toss a patch at transformers-compat that added .Compat modules with the changes to the transformers API over time, (like adding reader, state, writer combinators), I'd probably take the patch, but I don't have a definitive list of what they are and the design would involve some compromises.
I found another solution.
If alternative packages are an option you may also try my: http://hackage.haskell.org/package/explicit-exception
participants (22)
-
Chris Wong
-
Dan Burton
-
David Feuer
-
Edward A Kmett
-
Edward Kmett
-
Erik de Castro Lopo
-
Gregory Collins
-
Henning Thielemann
-
Henning Thielemann
-
Herbert Valerio Riedel
-
Index Int
-
John Wiegley
-
Kei Hibino
-
Mario Blažević
-
Michael Snoyman
-
Niklas Hambüchen
-
Roman Cheplyaka
-
Ross Paterson
-
Ross Paterson
-
Simon Hengel
-
Vincent Hanquez
-
wren ng thornton