[GHC] #12160: MonadFail instance for (Either String)?

#12160: MonadFail instance for (Either String)? -------------------------------------+------------------------------------- Reporter: lexi.lambda | Owner: Type: feature | Status: new request | Priority: normal | Milestone: Component: libraries | Version: 8.0.1 (other) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I think one of the cool things about breaking out `MonadFail` would be the opportunity to introduce an instance for `Either String`, which isn’t possible to do with plain `Monad` without overlapping instances. The instance itself would be completely trivial: {{{#!hs instance MonadFail (Either String) where fail = Left }}} The only possible reason to ''not'' do this, as far as I can tell, would be because it requires `FlexibleInstances`. This already seems to be used for a few instances in `base`, and it seems like it would be extremely useful, so I would really appreciate if such an instance was defined. I’d be happy to submit a patch to add it, but I wasn’t sure if this would be an uncontroversial change or not. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12160 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12160: MonadFail instance for (Either String)? -------------------------------------+------------------------------------- Reporter: lexi.lambda | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: libraries | Version: 8.0.1 (other) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): Sounds like a good idea to me, but there might be issues (such as breaking compatibility with the current `Monad` instance for `Either`). I suggest you propose this formally, as described in https://wiki.haskell.org/Library_submissions, and see what the collective wisdom of the community thinks of this. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12160#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12160: MonadFail instance for (Either String)? -------------------------------------+------------------------------------- Reporter: lexi.lambda | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: libraries | Version: 8.0.1 (other) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Let's make it {{{#!hs instance String ~ a => MonadFail (Either a) where fail = Left }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12160#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12160: MonadFail instance for (Either String)? -------------------------------------+------------------------------------- Reporter: lexi.lambda | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: libraries | Version: 8.0.1 (other) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Otherwise {{{#!hs [Right (), fail "bye"] :: MonadFail (Either a) => [Either a ()] }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12160#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12160: MonadFail instance for (Either String)? -------------------------------------+------------------------------------- Reporter: lexi.lambda | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: libraries | Version: 8.0.1 (other) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by lexi.lambda): Ah, that’s a good point, though I don’t think I agree with it. I’m imagining `text` defining a `MonadFail (Either Text)` instance, for example, and it seems like it wouldn’t be all that worth it to prevent that kind of instance just to help out type inference in a couple cases. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12160#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12160: MonadFail instance for (Either String)? -------------------------------------+------------------------------------- Reporter: lexi.lambda | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: libraries | Version: 8.0.1 (other) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Do you have a use case? I don't think details of string conversion belong in the `MonadError` instances and if you want instances like `MonadFail (Either ByteString)` that brings up issues of encoding, truncation (as `IsString ByteString`). It would complicate the type class and make inference fail in basic examples {{{#!hs data Foobar = Foo Int | Bar String instance MonadFail (Either String) where fail = Left }}} {{{ ghci> do Bar a <- Right (Foo 42) ghci| pure a ghci| <interactive>:13:1: error: • Ambiguous type variable ‘a0’ arising from a use of ‘print’ prevents the constraint ‘(Show a0)’ from being solved. ... }}} I argue most users would prefer {{{#!hs instance String ~ a => MonadFail (Either a) where fail = Left }}} {{{ ghci> do Bar a <- Right (Foo 42) ghci| pure a ghci| Left "Pattern match failure in do expression at <interactive>:11:4-8" }}} and if they want to avoid `String` entirely they can use `throwError` from [https://hackage.haskell.org/package/mtl-2.2.1/docs/Control-Monad- Except.html#t:MonadError MonadError] and be polymorphic in the error {{{#!hs throwError :: e -> Either e a throwError @String @(Either _) :: String -> Either String a throwError @Text @(Either _) :: Text -> Either Text a throwError @[Bool] @(Either _) :: [Bool] -> Either [Bool] a }}} {{{#!hs instance MonadError e (Either e) where throwError :: e -> Either e a throwError = Left catchError :: Either e a -> (e -> Either e a) -> Either e a Left l `catchError` h = h l Right r `catchError` _ = Right r }}} ---- This may be what you were aiming at, {{{#!hs instance IsString str => MonadFail (Either str) where fail :: String -> Either str a fail = Left . fromString -- Left "Pattern match failure in do expression at /tmp/tH2v.hs:16:3-7" str :: Either String String str = do Bar a <- Right (Foo 42); pure a -- Left "Pattern match failure in do expression at /tmp/tH2v.hs:21:3-7" txt :: Either Text String txt = do Bar a <- Right (Foo 42); pure a -- Left (Const (Identity "Pattern match failure in do expression at /tmp/tH2v.hs:26:3-7")) cnst :: Either (Const (Identity [Char]) ()) String cnst = do Bar a <- Right (Foo 42); pure a }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12160#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12160: MonadFail instance for (Either String)? -------------------------------------+------------------------------------- Reporter: lexi.lambda | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: libraries | Version: 8.0.1 (other) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by lexi.lambda): Your point about just using `IsString` makes sense to me, so maybe that would be better, instead. One of the reasons `MonadFail` might sometimes be desirable over `MonadError` is that `MonadError` does not make it possible to make a single expression generic over both `Either` ''and'' `IO`, unless the `Either` type is `Either IOException a`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12160#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12160: MonadFail instance for (Either String)? -------------------------------------+------------------------------------- Reporter: lexi.lambda | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: libraries | Version: 8.0.1 (other) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9588 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by Iceland_jack): * related: => #9588 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12160#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12160: MonadFail instance for (Either String)? -------------------------------------+------------------------------------- Reporter: lexi.lambda | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: libraries | Version: 8.0.1 (other) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9588 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ekmett): The danger here is that the `(Either String)` specific instance proposed here rules out reasoning uniformly about any other instance someone might want to put on `Either` that works for more types, which could get to be be common in things like test suites. This lets one 'pointwise' instance override anybody's ability to grab a more general one. e.g. the old `Error` class from `MonadError` approach. I'm not advocating for that class per se, as there is no need for `noMsg` for `MonadFail`, making that class "too big". `IsString` on the other hand, does have the remarkable property that it has precisely the right size. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12160#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12160: MonadFail instance for (Either String)? -------------------------------------+------------------------------------- Reporter: lexi.lambda | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: libraries | Version: 8.0.1 (other) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9588 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by hesiod): * cc: ekmett (added) Comment: So if I understood you right, ekmett, you would be fine with Iceland_jack's approach, i.e. `instance IsString str => MonadFail (Either str)`? In that case, I'd be glad to assemble a patch provided there are no other concerns remaining. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12160#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12160: MonadFail instance for (Either String)? -------------------------------------+------------------------------------- Reporter: lexi.lambda | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: libraries | Version: 8.0.1 (other) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9588 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ekmett): I support the instance, but this should go out as a real libraries proposal to the libraries@ mailing list, rather than being decided and acted on in relative isolation here. If you want to kickstart that process I'll happily toss in a +1. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12160#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12160: MonadFail instance for (Either String)? -------------------------------------+------------------------------------- Reporter: lexi.lambda | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: libraries | Version: 8.0.1 (other) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9588 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by hesiod): Ok, will do. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12160#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12160: MonadFail instance for (Either String)? -------------------------------------+------------------------------------- Reporter: lexi.lambda | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: libraries | Version: 8.0.1 (other) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9588 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by hesiod): I tried implementing this, however, simply adding the instance in Data.Either leads to an import cycle because {{{Data.String(IsString(..))}}} has to be imported: {{{ Module imports form a cycle: module ‘Data.Either’ (libraries/base/Data/Either.hs) imports ‘Data.String’ (libraries/base/Data/String.hs) which imports ‘Data.List’ (libraries/base/Data/List.hs) which imports ‘Data.Traversable’ (libraries/base/Data/Traversable.hs) which imports ‘Data.Either’ (libraries/base/Data/Either.hs) }}} However, I can't investigate this further atm, so if anyone wants to pick this up, please go ahead. I guess some shuffling around (maybe creating a hidden module for IsString) should solve the issue. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12160#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12160: MonadFail instance for (Either String)? -------------------------------------+------------------------------------- Reporter: lexi.lambda | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: libraries | Version: 8.0.1 (other) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9588 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by sjakobi): * cc: sjakobi (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12160#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12160: MonadFail instance for (Either String)? -------------------------------------+------------------------------------- Reporter: lexi.lambda | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: libraries | Version: 8.0.1 (other) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9588 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ekmett): I suppose you'd need to invert the Data.Either -> Data.String import. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12160#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12160: MonadFail instance for (Either String)? -------------------------------------+------------------------------------- Reporter: lexi.lambda | Owner: (none) Type: feature request | Status: closed Priority: normal | Milestone: Component: libraries | Version: 8.0.1 (other) | Resolution: wontfix | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9588 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by dmbergey): * status: new => closed * resolution: => wontfix Comment: As of 2018, the libraries committee has rejected this change. The mailing list discussion is at: https://mail.haskell.org/pipermail/libraries/2018-October/028988.html The concerns are that: - the instances "get in the way of a user who wants to treat the parameter uniformly" - `IsString` is too far from standard Haskell (and unlikely to be added to the standard) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12160#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC