Skip to content

Commit

Permalink
Fix KillSignal arg; add fromKillSignal (#51)
Browse files Browse the repository at this point in the history
* Add fromKillSignal

* Fix kill signal arg
  • Loading branch information
JordanMartinez authored Jul 25, 2023
1 parent c3f8b99 commit 5e867de
Show file tree
Hide file tree
Showing 6 changed files with 58 additions and 12 deletions.
12 changes: 11 additions & 1 deletion CHANGELOG.md
Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,17 @@ Bugfixes:

Other improvements:

## [v10.1.0](https://github.com/purescript-node/purescript-node-child-process/releases/tag/v10.1.0) - 2023-07-25
## [v11.0.0](https://github.com/purescript-node/purescript-node-child-process/releases/tag/v11.0.0) - 2023-07-25

Breaking changes:
- Update the signal arg from `String` to `KillSignal` (#51 by @JordanMartinez)

- `Exit`'s `BySignal` constructor's arg
- `exitH`/`closeH`'s signal arg
- `spawnSync`'s `SpawnResult`'s `signal` field

New features:
- Added `fromKillSignal` (#51 by @JordanMartinez)

Other improvements:
- Fix regression: add `ref`/`unref` APIs that were dropped in `v10.0.0` (#50 by @JordanMartinez)
Expand Down
6 changes: 6 additions & 0 deletions src/Node/ChildProcess/Types.js
Original file line number Diff line number Diff line change
@@ -0,0 +1,6 @@
export const fromKillSignalImpl = (left, right, sig) => {
const ty = typeof sig;
if (ty === "number") return right(sig | 0);
if (ty === "string") return left(sig);
throw new Error("Impossible. Got kill signal that was neither int nor string: " + sig);
};
35 changes: 32 additions & 3 deletions src/Node/ChildProcess/Types.purs
Original file line number Diff line number Diff line change
@@ -1,7 +1,31 @@
module Node.ChildProcess.Types where
module Node.ChildProcess.Types
( UnsafeChildProcess
, Handle
, StdIO
, pipe
, ignore
, overlapped
, ipc
, inherit
, shareStream
, fileDescriptor
, fileDescriptor'
, defaultStdIO
, KillSignal
, intSignal
, stringSignal
, fromKillSignal
, Shell
, enableShell
, customShell
, StringOrBuffer
, Exit(..)
) where

import Prelude

import Data.Either (Either(..), either)
import Data.Function.Uncurried (Fn3, runFn3)
import Data.Nullable (Nullable, null)
import Node.FS (FileDescriptor)
import Node.Stream (Stream)
Expand Down Expand Up @@ -54,6 +78,11 @@ intSignal = unsafeCoerce
stringSignal :: String -> KillSignal
stringSignal = unsafeCoerce

fromKillSignal :: KillSignal -> Either Int String
fromKillSignal sig = runFn3 fromKillSignalImpl Left Right sig

foreign import fromKillSignalImpl :: Fn3 (forall l r. l -> Either l r) (forall l r. r -> Either l r) (KillSignal) (Either Int String)

foreign import data Shell :: Type

enableShell :: Shell
Expand All @@ -70,8 +99,8 @@ foreign import data StringOrBuffer :: Type
-- | due to a signal.
data Exit
= Normally Int
| BySignal String
| BySignal KillSignal

instance showExit :: Show Exit where
show (Normally x) = "Normally " <> show x
show (BySignal sig) = "BySignal " <> show sig
show (BySignal sig) = "BySignal " <> (either show show $ fromKillSignal sig)
10 changes: 5 additions & 5 deletions src/Node/UnsafeChildProcess/Safe.purs
Original file line number Diff line number Diff line change
Expand Up @@ -36,7 +36,7 @@ import Data.Posix.Signal as Signal
import Effect (Effect)
import Effect.Uncurried (EffectFn1, EffectFn2, mkEffectFn1, mkEffectFn2, runEffectFn1, runEffectFn2)
import Foreign (Foreign)
import Node.ChildProcess.Types (Exit(..), Handle, StdIO, UnsafeChildProcess, ipc, pipe)
import Node.ChildProcess.Types (Exit(..), Handle, KillSignal, StdIO, UnsafeChildProcess, ipc, pipe)
import Node.Errors.SystemError (SystemError)
import Node.EventEmitter (EventEmitter, EventHandle(..))
import Node.EventEmitter.UtilTypes (EventHandle0, EventHandle1)
Expand All @@ -46,25 +46,25 @@ import Unsafe.Coerce (unsafeCoerce)
toEventEmitter :: UnsafeChildProcess -> EventEmitter
toEventEmitter = unsafeCoerce

closeH :: EventHandle UnsafeChildProcess (Exit -> Effect Unit) (EffectFn2 (Nullable Int) (Nullable String) Unit)
closeH :: EventHandle UnsafeChildProcess (Exit -> Effect Unit) (EffectFn2 (Nullable Int) (Nullable KillSignal) Unit)
closeH = EventHandle "close" \cb -> mkEffectFn2 \code signal ->
case toMaybe code, toMaybe signal of
Just c, _ -> cb $ Normally c
_, Just s -> cb $ BySignal s
_, _ -> unsafeCrashWith $ "Impossible. 'close' event did not get an exit code or kill signal: " <> show code <> "; " <> show signal
_, _ -> unsafeCrashWith $ "Impossible. 'close' event did not get an exit code or kill signal: " <> show code <> "; " <> (unsafeCoerce signal)

disconnectH :: EventHandle0 UnsafeChildProcess
disconnectH = EventHandle "disconnect" identity

errorH :: EventHandle1 UnsafeChildProcess SystemError
errorH = EventHandle "error" mkEffectFn1

exitH :: EventHandle UnsafeChildProcess (Exit -> Effect Unit) (EffectFn2 (Nullable Int) (Nullable String) Unit)
exitH :: EventHandle UnsafeChildProcess (Exit -> Effect Unit) (EffectFn2 (Nullable Int) (Nullable KillSignal) Unit)
exitH = EventHandle "exitH" \cb -> mkEffectFn2 \code signal ->
case toMaybe code, toMaybe signal of
Just c, _ -> cb $ Normally c
_, Just s -> cb $ BySignal s
_, _ -> unsafeCrashWith $ "Impossible. 'exit' event did not get an exit code or kill signal: " <> show code <> "; " <> show signal
_, _ -> unsafeCrashWith $ "Impossible. 'exit' event did not get an exit code or kill signal: " <> show code <> "; " <> (unsafeCoerce signal)

messageH :: EventHandle UnsafeChildProcess (Foreign -> Maybe Handle -> Effect Unit) (EffectFn2 Foreign (Nullable Handle) Unit)
messageH = EventHandle "message" \cb -> mkEffectFn2 \a b -> cb a $ toMaybe b
Expand Down
2 changes: 1 addition & 1 deletion src/Node/UnsafeChildProcess/Unsafe.purs
Original file line number Diff line number Diff line change
Expand Up @@ -290,7 +290,7 @@ type JsSpawnSyncResult =
, stdout :: StringOrBuffer
, stderr :: StringOrBuffer
, status :: Nullable Int
, signal :: Nullable String
, signal :: Nullable KillSignal
, error :: Nullable SystemError
}

Expand Down
5 changes: 3 additions & 2 deletions test/Main.purs
Original file line number Diff line number Diff line change
Expand Up @@ -2,14 +2,15 @@ module Test.Main where

import Prelude

import Data.Either (hush)
import Data.Maybe (Maybe(..))
import Data.Posix.Signal (Signal(..))
import Data.Posix.Signal as Signal
import Effect (Effect)
import Effect.Console (log)
import Node.Buffer as Buffer
import Node.ChildProcess (errorH, exec', execSync', exitH, kill, spawn, stdout)
import Node.ChildProcess.Types (Exit(..))
import Node.ChildProcess.Types (Exit(..), fromKillSignal)
import Node.Encoding (Encoding(..))
import Node.Encoding as NE
import Node.Errors.SystemError (code)
Expand Down Expand Up @@ -40,7 +41,7 @@ main = do
_ <- kill ls
ls # on_ exitH \exit ->
case exit of
BySignal s | Just SIGTERM <- Signal.fromString s ->
BySignal s | Just SIGTERM <- Signal.fromString =<< (hush $ fromKillSignal s) ->
log "All good!"
_ -> do
log ("Bad exit: expected `BySignal SIGTERM`, got: " <> show exit)
Expand Down

0 comments on commit 5e867de

Please sign in to comment.