#7229: Detecting if a process was killed by a signal is impossible
----------------------------------+-----------------------------------------
    Reporter:  benmachine         |       Owner:                  
        Type:  bug                |      Status:  new             
    Priority:  high               |   Milestone:  7.6.2           
   Component:  libraries/process  |     Version:                  
    Keywords:                     |          Os:  Unknown/Multiple
Architecture:  Unknown/Multiple   |     Failure:  None/Unknown    
  Difficulty:  Unknown            |    Testcase:                  
   Blockedby:                     |    Blocking:                  
     Related:                     |  
----------------------------------+-----------------------------------------

Comment(by simonmar):

 Ok, points taken.  128+signal is not good, because that overlaps with exit
 codes.

 Unfortunately we can't add the right information to `ExitCode`, because it
 is a platform-independent type.  The correct type already exists: it is
 called `System.Posix.ProcessStatus`.

 {{{
 data ProcessStatus = Exited ExitCode
                    | Terminated Signal
                    | Stopped Signal
                    deriving (Eq, Ord, Show)
 }}}

 Unfortunately whoever wrote this forgot to add a `Bool` to indicate a core
 dump in the `Terminated` constructor.  We *could* fix that.

 Now, the right thing to do would be to create a new `process-unix` package
 containing

 {{{
 module System.Process.Posix where
 waitForProcess :: ProcessHandle -> IO ProcessStatus
 getProcessStatus :: ProcessHandle -> IO (Maybe ProcessStatus)
 }}}

 It can't be part of the `process` package because the API of a package
 cannot differ depending on the platform.  It could be part of the `unix`
 package, but then we have to move a chunk of code from the `process`
 package into the `unix` package, which is annoying.


 I propose as an intermediate solution that we just fix the `ExitCode`
 encoding: instead of 128+signal, use `(signal << 8) + exit code`, with a
 core dump setting the `0x8000` bit.

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/7229#comment:6>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler

_______________________________________________
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to