[GHC] #14349: Semigroup/Monoid instances for System.Exit.ExitCode

#14349: Semigroup/Monoid instances for System.Exit.ExitCode -------------------------------------+------------------------------------- Reporter: neil.mayhew | Owner: (none) Type: feature | Status: new request | Priority: low | Milestone: Component: | Version: 8.2.1 libraries/base | 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: -------------------------------------+------------------------------------- Please add instances for ExitCode along the following lines: {{{#!hs instance Monoid ExitCode where mempty = ExitSuccess mappend ExitSuccess b = b mappend a _ = a }}} This allows the summary result of multiple child processes to be computed naturally. For example: {{{#!hs mconcat <$> mapM system commands }}} The result is `ExitSuccess` if they all succeeded, and the leftmost failure otherwise -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14349 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14349: Semigroup/Monoid instances for System.Exit.ExitCode -------------------------------------+------------------------------------- Reporter: neil.mayhew | Owner: (none) Type: feature request | Status: upstream Priority: low | Milestone: Component: libraries/base | Version: 8.2.1 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: | -------------------------------------+------------------------------------- Changes (by bgamari): * cc: hvr, ekmett, core-libraries-committee@… (added) * status: new => upstream Comment: I think I would like to defer to the Core Libraries Committee on this. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14349#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14349: Semigroup/Monoid instances for System.Exit.ExitCode -------------------------------------+------------------------------------- Reporter: neil.mayhew | Owner: (none) Type: feature request | Status: upstream Priority: low | Milestone: Component: libraries/base | Version: 8.2.1 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: | -------------------------------------+------------------------------------- Changes (by neil.mayhew): * cc: hvr, ekmett, core-libraries-committee@… (removed) Old description:
Please add instances for ExitCode along the following lines:
{{{#!hs instance Monoid ExitCode where mempty = ExitSuccess mappend ExitSuccess b = b mappend a _ = a }}}
This allows the summary result of multiple child processes to be computed naturally. For example:
{{{#!hs mconcat <$> mapM system commands }}}
The result is `ExitSuccess` if they all succeeded, and the leftmost failure otherwise
New description: Please add instances for ExitCode along the following lines: {{{#!hs instance Monoid ExitCode where mempty = ExitSuccess mappend ExitSuccess b = b mappend a _ = a }}} This allows the summary result of multiple child processes to be computed naturally. For example: {{{#!hs mconcat <$> mapM system commands }}} The result is `ExitSuccess` if they all succeeded, and the leftmost failure otherwise. This is similar to the behaviour of `set -e` in `bash`. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14349#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14349: Semigroup/Monoid instances for System.Exit.ExitCode -------------------------------------+------------------------------------- Reporter: neil.mayhew | Owner: (none) Type: feature request | Status: upstream Priority: low | Milestone: Component: libraries/base | Version: 8.2.1 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): I am not yet convinced. Is this the only sensible `Monoid` instance? Do we want to see code that says `returnWith mempty`? Why is leftmost the right thing? Note that it is verymuch noch like `set -e` because `set -e` *stops* after the first error. Maybe a named function `anySuccess :: [ExitCode] -> ExitCode` would be a better design. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14349#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14349: Semigroup/Monoid instances for System.Exit.ExitCode -------------------------------------+------------------------------------- Reporter: neil.mayhew | Owner: (none) Type: feature request | Status: upstream Priority: low | Milestone: Component: libraries/base | Version: 8.2.1 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: | -------------------------------------+------------------------------------- Changes (by neil.mayhew): * cc: hvr, ekmett, core-libraries-committee (added) Comment: As far as I can see, the only other reasonable `Monoid` instance would be to have success if any succeeded, but this is almost never what you want. It would be possible to use a similar approach to the `Any`/`All` newtypes for `Bool`, but this seems like overthinking it. It would be possible to favour the rightmost failure, but I don't see much point in this. That's why I mentioned `set -e`, which returns the exit code of the first, ie leftmost, failure. The fact that bash short-circuits the rest of the evaluation is mostly an issue of lazy evaluation. The semantics of the summary exit code are the same, although of course the side effects are different. Adding a named function would be a valid approach, but it's a pity to add a single-use function when we already have a nice general way to view the problem with `Monoid`. If `mempty` is an issue then it could be a `Semigroup` instance. However, it seems natural to me that running no child processes is considered successful. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14349#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14349: Semigroup/Monoid instances for System.Exit.ExitCode -------------------------------------+------------------------------------- Reporter: neil.mayhew | Owner: (none) Type: feature request | Status: upstream Priority: low | Milestone: Component: libraries/base | Version: 8.2.1 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 glguy): Having a Monoid instance doesn't seem like a good idea to me. The code above could be written more clearly using an explicitly named, locally defined operation: `combineExitCodes <$> mapM system commands`. Reusing `mconcat` isn't a win here. Having such a forced Monoid instance simply means that users will have to consult the documentation to find the instance declaration to determine what behavior it has. There isn't a natural meaning for `instance Monoid ExitCode` -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14349#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14349: Semigroup/Monoid instances for System.Exit.ExitCode -------------------------------------+------------------------------------- Reporter: neil.mayhew | Owner: (none) Type: feature request | Status: upstream Priority: low | Milestone: Component: libraries/base | Version: 8.2.1 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 neil.mayhew): I don't see this as 'forced'. The meaning I'm suggesting is the conventional interpretation of OS exit statuses, ie a set of processes is considered failed if any one of them fails. The only reason to look up the documentation would be if someone needs to know how the `Int` in `ExitFailure Int` is produced, and typically people don't care about the value, just success or failure. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14349#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14349: Semigroup/Monoid instances for System.Exit.ExitCode -------------------------------------+------------------------------------- Reporter: neil.mayhew | Owner: (none) Type: feature request | Status: upstream Priority: low | Milestone: Component: libraries/base | Version: 8.2.1 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 neil.mayhew): Maybe it would help to mention my use case, which is running a set of regression tests implemented as shell commands. (They pipe the output of an executable into a `diff` against the expected output. The exit status of the shell command is that of the `diff`.) The program that runs the regression tests is then used as a Cabal test suite (of type `exitcode- stdio`). (A simplified version of) the code looks like this: {{{#!hs {-# OPTIONS_GHC -fno-warn-orphans #-} import Data.Monoid (Monoid(..)) import System.Process (system) import System.Exit (ExitCode(..), exitWith) instance Monoid ExitCode where mempty = ExitSuccess mappend ExitSuccess b = b mappend a _ = a data MyTest = MyTest String tests :: [MyTest] tests = map MyTest [ "echo Test1" , "echo Test2" , "exit 3" , "echo Test4" , "exit 5" ] main :: IO () main = mapM runTest tests >>= exitWith . mconcat runTest :: MyTest -> IO ExitCode runTest (MyTest cmd) = system cmd }}} To avoid the `Monoid` instance I could have the `runTest` function return a `Bool` instead, and use `and` to collect all the statuses: {{{#!hs main :: IO () main = mapM runTest tests >>= bool exitFailure exitSuccess . and runTest :: MyTest -> IO Bool runTest (MyTest cmd) = (==ExitSuccess) <$> system cmd }}} However, the `Monoid` approach is more elegant because it avoids the repeated and redundant use of machinery from `System.Exit`. In both cases, the exit code of the test suite is `3`. It also happens that the `diff` output appears in the output of the test suite, and all the tests are run, rather than stopping at the first failure. So the output of the simplified test suite above is: {{{ Test1 Test2 Test4 }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14349#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14349: Semigroup/Monoid instances for System.Exit.ExitCode -------------------------------------+------------------------------------- Reporter: neil.mayhew | Owner: (none) Type: feature request | Status: upstream Priority: low | Milestone: Component: libraries/base | Version: 8.2.1 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 neil.mayhew): Actually, in the second version, the exit code is `1`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14349#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14349: Semigroup/Monoid instances for System.Exit.ExitCode -------------------------------------+------------------------------------- Reporter: neil.mayhew | Owner: (none) Type: feature request | Status: upstream Priority: low | Milestone: Component: libraries/base | Version: 8.2.1 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 neil.mayhew): Since there's been no further discussion, I'll assume that's a no to my monoid proposal. However, I've been thinking about it some more, and I've come up with a solution that I think will be more acceptable (based on previous comments). Since `ExitCode` is structurally identical to `Maybe Int`, and since `Maybe` already has a lot of useful typeclass instances, I propose an isomorphism as follows: {{{#!hs -- | Case analysis for the 'ExitCode' type exitCode :: a -> (Int -> a) -> ExitCode -> a exitCode x _ ExitSuccess = x exitCode _ f (ExitFailure i) = f i exitCodeToMaybe :: ExitCode -> Maybe Int exitCodeToMaybe = exitCode Nothing Just maybeToExitCode :: Maybe Int -> ExitCode maybeToExitCode = maybe ExitSuccess ExitFailure }}} Then it would be possible to use `Monoid` instances of newtype wrappers such as `First/Last` or use `Maybe`'s `MonadPlus` or `Alternative` instances. In particular, `msum`/`asum` has the behaviour I'm looking for: {{{#!hs
msum [Nothing, Just 1, Nothing, Just 3] Just 1 }}}
This would allow the following: {{{#!hs exitWith . maybeToExitCode . msum $ mapM (exitCodeToMaybe <$> system) commands }}} This could be further cleaned up: {{{#!hs exitWith' :: Maybe Int -> IO () exitWith' = exitWith . maybeToExitCode system' :: String -> IO (Maybe Int) system' = exitCodeToMaybe <$> system main = exitWith' . msum . mapM system' $ commands }}} I would be in favour of providing `exitWith'` in `System.Exit` (eg as `exitWithMaybe`) but it's less easy to argue that `system'` should be provided (eg as `systemWithMaybe`) because there are several other functions in `System.Process` that return an `ExitCode` and it would be awkward to provide `Maybe` variants of all of them. So, is adding the isomorphism functions a possibility? What about `exitWithMaybe`? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14349#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC