module Z.IO.Network.IPC (
IPCClientConfig(..)
, UVStream
, defaultIPCClientConfig
, initIPCClient
, IPCServerConfig(..)
, defaultIPCServerConfig
, startIPCServer
, helloWorld
, echo
, initIPCStream
) where
import Control.Monad
import Control.Monad.IO.Class
import GHC.Generics
import Z.Data.CBytes
import Z.Data.Text.Print (Print)
import Z.Data.JSON (JSON)
import Z.IO.Exception
import Z.IO.Resource
import Z.IO.Network.TCP (startServerLoop)
import Z.IO.UV.FFI
import Z.IO.UV.Manager
import Z.IO.UV.UVStream
data IPCClientConfig = IPCClientConfig
{ IPCClientConfig -> Maybe CBytes
ipcClientName :: Maybe CBytes
, IPCClientConfig -> CBytes
ipcTargetName :: CBytes
} deriving (IPCClientConfig -> IPCClientConfig -> Bool
(IPCClientConfig -> IPCClientConfig -> Bool)
-> (IPCClientConfig -> IPCClientConfig -> Bool)
-> Eq IPCClientConfig
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IPCClientConfig -> IPCClientConfig -> Bool
$c/= :: IPCClientConfig -> IPCClientConfig -> Bool
== :: IPCClientConfig -> IPCClientConfig -> Bool
$c== :: IPCClientConfig -> IPCClientConfig -> Bool
Eq, Eq IPCClientConfig
Eq IPCClientConfig
-> (IPCClientConfig -> IPCClientConfig -> Ordering)
-> (IPCClientConfig -> IPCClientConfig -> Bool)
-> (IPCClientConfig -> IPCClientConfig -> Bool)
-> (IPCClientConfig -> IPCClientConfig -> Bool)
-> (IPCClientConfig -> IPCClientConfig -> Bool)
-> (IPCClientConfig -> IPCClientConfig -> IPCClientConfig)
-> (IPCClientConfig -> IPCClientConfig -> IPCClientConfig)
-> Ord IPCClientConfig
IPCClientConfig -> IPCClientConfig -> Bool
IPCClientConfig -> IPCClientConfig -> Ordering
IPCClientConfig -> IPCClientConfig -> IPCClientConfig
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: IPCClientConfig -> IPCClientConfig -> IPCClientConfig
$cmin :: IPCClientConfig -> IPCClientConfig -> IPCClientConfig
max :: IPCClientConfig -> IPCClientConfig -> IPCClientConfig
$cmax :: IPCClientConfig -> IPCClientConfig -> IPCClientConfig
>= :: IPCClientConfig -> IPCClientConfig -> Bool
$c>= :: IPCClientConfig -> IPCClientConfig -> Bool
> :: IPCClientConfig -> IPCClientConfig -> Bool
$c> :: IPCClientConfig -> IPCClientConfig -> Bool
<= :: IPCClientConfig -> IPCClientConfig -> Bool
$c<= :: IPCClientConfig -> IPCClientConfig -> Bool
< :: IPCClientConfig -> IPCClientConfig -> Bool
$c< :: IPCClientConfig -> IPCClientConfig -> Bool
compare :: IPCClientConfig -> IPCClientConfig -> Ordering
$ccompare :: IPCClientConfig -> IPCClientConfig -> Ordering
$cp1Ord :: Eq IPCClientConfig
Ord, Int -> IPCClientConfig -> ShowS
[IPCClientConfig] -> ShowS
IPCClientConfig -> String
(Int -> IPCClientConfig -> ShowS)
-> (IPCClientConfig -> String)
-> ([IPCClientConfig] -> ShowS)
-> Show IPCClientConfig
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IPCClientConfig] -> ShowS
$cshowList :: [IPCClientConfig] -> ShowS
show :: IPCClientConfig -> String
$cshow :: IPCClientConfig -> String
showsPrec :: Int -> IPCClientConfig -> ShowS
$cshowsPrec :: Int -> IPCClientConfig -> ShowS
Show, ReadPrec [IPCClientConfig]
ReadPrec IPCClientConfig
Int -> ReadS IPCClientConfig
ReadS [IPCClientConfig]
(Int -> ReadS IPCClientConfig)
-> ReadS [IPCClientConfig]
-> ReadPrec IPCClientConfig
-> ReadPrec [IPCClientConfig]
-> Read IPCClientConfig
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [IPCClientConfig]
$creadListPrec :: ReadPrec [IPCClientConfig]
readPrec :: ReadPrec IPCClientConfig
$creadPrec :: ReadPrec IPCClientConfig
readList :: ReadS [IPCClientConfig]
$creadList :: ReadS [IPCClientConfig]
readsPrec :: Int -> ReadS IPCClientConfig
$creadsPrec :: Int -> ReadS IPCClientConfig
Read, (forall x. IPCClientConfig -> Rep IPCClientConfig x)
-> (forall x. Rep IPCClientConfig x -> IPCClientConfig)
-> Generic IPCClientConfig
forall x. Rep IPCClientConfig x -> IPCClientConfig
forall x. IPCClientConfig -> Rep IPCClientConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep IPCClientConfig x -> IPCClientConfig
$cfrom :: forall x. IPCClientConfig -> Rep IPCClientConfig x
Generic)
deriving anyclass (Int -> IPCClientConfig -> Builder ()
(Int -> IPCClientConfig -> Builder ()) -> Print IPCClientConfig
forall a. (Int -> a -> Builder ()) -> Print a
toUTF8BuilderP :: Int -> IPCClientConfig -> Builder ()
$ctoUTF8BuilderP :: Int -> IPCClientConfig -> Builder ()
Print, Value -> Converter IPCClientConfig
IPCClientConfig -> Value
IPCClientConfig -> Builder ()
(Value -> Converter IPCClientConfig)
-> (IPCClientConfig -> Value)
-> (IPCClientConfig -> Builder ())
-> JSON IPCClientConfig
forall a.
(Value -> Converter a)
-> (a -> Value) -> (a -> Builder ()) -> JSON a
encodeJSON :: IPCClientConfig -> Builder ()
$cencodeJSON :: IPCClientConfig -> Builder ()
toValue :: IPCClientConfig -> Value
$ctoValue :: IPCClientConfig -> Value
fromValue :: Value -> Converter IPCClientConfig
$cfromValue :: Value -> Converter IPCClientConfig
JSON)
defaultIPCClientConfig :: IPCClientConfig
defaultIPCClientConfig :: IPCClientConfig
defaultIPCClientConfig = Maybe CBytes -> CBytes -> IPCClientConfig
IPCClientConfig Maybe CBytes
forall a. Maybe a
Nothing CBytes
"./ipc"
initIPCClient :: IPCClientConfig -> Resource UVStream
initIPCClient :: IPCClientConfig -> Resource UVStream
initIPCClient (IPCClientConfig Maybe CBytes
cname CBytes
tname) = do
UVManager
uvm <- IO UVManager -> Resource UVManager
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO UVManager
getUVManager
UVStream
client <- HasCallStack => UVManager -> Resource UVStream
UVManager -> Resource UVStream
initIPCStream UVManager
uvm
let hdl :: Ptr UVHandle
hdl = UVStream -> Ptr UVHandle
uvsHandle UVStream
client
IO () -> Resource ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> Resource ()) -> IO () -> Resource ()
forall a b. (a -> b) -> a -> b
$ do
Maybe CBytes -> (CBytes -> IO ()) -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ Maybe CBytes
cname ((CBytes -> IO ()) -> IO ()) -> (CBytes -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ CBytes
cname' ->
CBytes -> (BA# Word8 -> IO ()) -> IO ()
forall a. CBytes -> (BA# Word8 -> IO a) -> IO a
withCBytesUnsafe CBytes
cname' ((BA# Word8 -> IO ()) -> IO ()) -> (BA# Word8 -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ BA# Word8
cname_p ->
IO CInt -> IO ()
forall a. (HasCallStack, Integral a) => IO a -> IO ()
throwUVIfMinus_ (Ptr UVHandle -> BA# Word8 -> IO CInt
uv_pipe_bind Ptr UVHandle
hdl BA# Word8
cname_p)
CBytes -> (BA# Word8 -> IO ()) -> IO ()
forall a. CBytes -> (BA# Word8 -> IO a) -> IO a
withCBytesUnsafe CBytes
tname ((BA# Word8 -> IO ()) -> IO ()) -> (BA# Word8 -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ BA# Word8
tname_p -> do
IO Int -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IO Int -> IO ())
-> ((Ptr UVLoop -> IO UVSlotUnsafe) -> IO Int)
-> (Ptr UVLoop -> IO UVSlotUnsafe)
-> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HasCallStack =>
UVManager -> (Ptr UVLoop -> IO UVSlotUnsafe) -> IO Int
UVManager -> (Ptr UVLoop -> IO UVSlotUnsafe) -> IO Int
withUVRequest UVManager
uvm ((Ptr UVLoop -> IO UVSlotUnsafe) -> IO ())
-> (Ptr UVLoop -> IO UVSlotUnsafe) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ Ptr UVLoop
_ -> Ptr UVHandle -> BA# Word8 -> IO UVSlotUnsafe
hs_uv_pipe_connect Ptr UVHandle
hdl BA# Word8
tname_p
UVStream -> Resource UVStream
forall (m :: * -> *) a. Monad m => a -> m a
return UVStream
client
data IPCServerConfig = IPCServerConfig
{ IPCServerConfig -> CBytes
ipcListenName :: CBytes
, IPCServerConfig -> Int
ipcListenBacklog :: Int
} deriving (IPCServerConfig -> IPCServerConfig -> Bool
(IPCServerConfig -> IPCServerConfig -> Bool)
-> (IPCServerConfig -> IPCServerConfig -> Bool)
-> Eq IPCServerConfig
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IPCServerConfig -> IPCServerConfig -> Bool
$c/= :: IPCServerConfig -> IPCServerConfig -> Bool
== :: IPCServerConfig -> IPCServerConfig -> Bool
$c== :: IPCServerConfig -> IPCServerConfig -> Bool
Eq, Eq IPCServerConfig
Eq IPCServerConfig
-> (IPCServerConfig -> IPCServerConfig -> Ordering)
-> (IPCServerConfig -> IPCServerConfig -> Bool)
-> (IPCServerConfig -> IPCServerConfig -> Bool)
-> (IPCServerConfig -> IPCServerConfig -> Bool)
-> (IPCServerConfig -> IPCServerConfig -> Bool)
-> (IPCServerConfig -> IPCServerConfig -> IPCServerConfig)
-> (IPCServerConfig -> IPCServerConfig -> IPCServerConfig)
-> Ord IPCServerConfig
IPCServerConfig -> IPCServerConfig -> Bool
IPCServerConfig -> IPCServerConfig -> Ordering
IPCServerConfig -> IPCServerConfig -> IPCServerConfig
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: IPCServerConfig -> IPCServerConfig -> IPCServerConfig
$cmin :: IPCServerConfig -> IPCServerConfig -> IPCServerConfig
max :: IPCServerConfig -> IPCServerConfig -> IPCServerConfig
$cmax :: IPCServerConfig -> IPCServerConfig -> IPCServerConfig
>= :: IPCServerConfig -> IPCServerConfig -> Bool
$c>= :: IPCServerConfig -> IPCServerConfig -> Bool
> :: IPCServerConfig -> IPCServerConfig -> Bool
$c> :: IPCServerConfig -> IPCServerConfig -> Bool
<= :: IPCServerConfig -> IPCServerConfig -> Bool
$c<= :: IPCServerConfig -> IPCServerConfig -> Bool
< :: IPCServerConfig -> IPCServerConfig -> Bool
$c< :: IPCServerConfig -> IPCServerConfig -> Bool
compare :: IPCServerConfig -> IPCServerConfig -> Ordering
$ccompare :: IPCServerConfig -> IPCServerConfig -> Ordering
$cp1Ord :: Eq IPCServerConfig
Ord, Int -> IPCServerConfig -> ShowS
[IPCServerConfig] -> ShowS
IPCServerConfig -> String
(Int -> IPCServerConfig -> ShowS)
-> (IPCServerConfig -> String)
-> ([IPCServerConfig] -> ShowS)
-> Show IPCServerConfig
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IPCServerConfig] -> ShowS
$cshowList :: [IPCServerConfig] -> ShowS
show :: IPCServerConfig -> String
$cshow :: IPCServerConfig -> String
showsPrec :: Int -> IPCServerConfig -> ShowS
$cshowsPrec :: Int -> IPCServerConfig -> ShowS
Show, ReadPrec [IPCServerConfig]
ReadPrec IPCServerConfig
Int -> ReadS IPCServerConfig
ReadS [IPCServerConfig]
(Int -> ReadS IPCServerConfig)
-> ReadS [IPCServerConfig]
-> ReadPrec IPCServerConfig
-> ReadPrec [IPCServerConfig]
-> Read IPCServerConfig
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [IPCServerConfig]
$creadListPrec :: ReadPrec [IPCServerConfig]
readPrec :: ReadPrec IPCServerConfig
$creadPrec :: ReadPrec IPCServerConfig
readList :: ReadS [IPCServerConfig]
$creadList :: ReadS [IPCServerConfig]
readsPrec :: Int -> ReadS IPCServerConfig
$creadsPrec :: Int -> ReadS IPCServerConfig
Read, (forall x. IPCServerConfig -> Rep IPCServerConfig x)
-> (forall x. Rep IPCServerConfig x -> IPCServerConfig)
-> Generic IPCServerConfig
forall x. Rep IPCServerConfig x -> IPCServerConfig
forall x. IPCServerConfig -> Rep IPCServerConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep IPCServerConfig x -> IPCServerConfig
$cfrom :: forall x. IPCServerConfig -> Rep IPCServerConfig x
Generic)
deriving anyclass (Int -> IPCServerConfig -> Builder ()
(Int -> IPCServerConfig -> Builder ()) -> Print IPCServerConfig
forall a. (Int -> a -> Builder ()) -> Print a
toUTF8BuilderP :: Int -> IPCServerConfig -> Builder ()
$ctoUTF8BuilderP :: Int -> IPCServerConfig -> Builder ()
Print, Value -> Converter IPCServerConfig
IPCServerConfig -> Value
IPCServerConfig -> Builder ()
(Value -> Converter IPCServerConfig)
-> (IPCServerConfig -> Value)
-> (IPCServerConfig -> Builder ())
-> JSON IPCServerConfig
forall a.
(Value -> Converter a)
-> (a -> Value) -> (a -> Builder ()) -> JSON a
encodeJSON :: IPCServerConfig -> Builder ()
$cencodeJSON :: IPCServerConfig -> Builder ()
toValue :: IPCServerConfig -> Value
$ctoValue :: IPCServerConfig -> Value
fromValue :: Value -> Converter IPCServerConfig
$cfromValue :: Value -> Converter IPCServerConfig
JSON)
defaultIPCServerConfig :: IPCServerConfig
defaultIPCServerConfig :: IPCServerConfig
defaultIPCServerConfig = CBytes -> Int -> IPCServerConfig
IPCServerConfig
CBytes
"./ipc"
Int
256
startIPCServer :: HasCallStack
=> IPCServerConfig
-> (UVStream -> IO ())
-> IO ()
startIPCServer :: IPCServerConfig -> (UVStream -> IO ()) -> IO ()
startIPCServer IPCServerConfig{Int
CBytes
ipcListenBacklog :: Int
ipcListenName :: CBytes
ipcListenBacklog :: IPCServerConfig -> Int
ipcListenName :: IPCServerConfig -> CBytes
..} = HasCallStack =>
Int
-> (UVManager -> Resource UVStream)
-> (Ptr UVHandle -> IO ())
-> (CInt -> (UVStream -> IO ()) -> IO ())
-> (UVStream -> IO ())
-> IO ()
Int
-> (UVManager -> Resource UVStream)
-> (Ptr UVHandle -> IO ())
-> (CInt -> (UVStream -> IO ()) -> IO ())
-> (UVStream -> IO ())
-> IO ()
startServerLoop
(Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
ipcListenBacklog Int
128)
HasCallStack => UVManager -> Resource UVStream
UVManager -> Resource UVStream
initIPCStream
(\ Ptr UVHandle
serverHandle ->
CBytes -> (BA# Word8 -> IO ()) -> IO ()
forall a. CBytes -> (BA# Word8 -> IO a) -> IO a
withCBytesUnsafe CBytes
ipcListenName ((BA# Word8 -> IO ()) -> IO ()) -> (BA# Word8 -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ BA# Word8
name_p -> do
IO CInt -> IO ()
forall a. (HasCallStack, Integral a) => IO a -> IO ()
throwUVIfMinus_ (Ptr UVHandle -> BA# Word8 -> IO CInt
uv_pipe_bind Ptr UVHandle
serverHandle BA# Word8
name_p))
( \ CInt
fd UVStream -> IO ()
worker -> IO ThreadId -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IO ThreadId -> IO ()) -> (IO () -> IO ThreadId) -> IO () -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO () -> IO ThreadId
forkBa (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
UVManager
uvm <- IO UVManager
getUVManager
Resource UVStream -> (UVStream -> IO ()) -> IO ()
forall (m :: * -> *) a b.
(MonadMask m, MonadIO m, HasCallStack) =>
Resource a -> (a -> m b) -> m b
withResource (HasCallStack =>
(Ptr UVLoop -> Ptr UVHandle -> IO ())
-> UVManager -> Resource UVStream
(Ptr UVLoop -> Ptr UVHandle -> IO ())
-> UVManager -> Resource UVStream
initUVStream (\ Ptr UVLoop
loop Ptr UVHandle
hdl -> do
IO CInt -> IO ()
forall a. (HasCallStack, Integral a) => IO a -> IO ()
throwUVIfMinus_ (Ptr UVLoop -> Ptr UVHandle -> CInt -> IO CInt
uv_pipe_init Ptr UVLoop
loop Ptr UVHandle
hdl CInt
0)
IO CInt -> IO ()
forall a. (HasCallStack, Integral a) => IO a -> IO ()
throwUVIfMinus_ (Ptr UVHandle -> CInt -> IO CInt
uv_pipe_open Ptr UVHandle
hdl CInt
fd)) UVManager
uvm) ((UVStream -> IO ()) -> IO ()) -> (UVStream -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ UVStream
uvs -> do
UVStream -> IO ()
worker UVStream
uvs)
initIPCStream :: HasCallStack => UVManager -> Resource UVStream
initIPCStream :: UVManager -> Resource UVStream
initIPCStream = HasCallStack =>
(Ptr UVLoop -> Ptr UVHandle -> IO ())
-> UVManager -> Resource UVStream
(Ptr UVLoop -> Ptr UVHandle -> IO ())
-> UVManager -> Resource UVStream
initUVStream (\ Ptr UVLoop
loop Ptr UVHandle
hdl ->
IO CInt -> IO ()
forall a. (HasCallStack, Integral a) => IO a -> IO ()
throwUVIfMinus_ (Ptr UVLoop -> Ptr UVHandle -> CInt -> IO CInt
uv_pipe_init Ptr UVLoop
loop Ptr UVHandle
hdl CInt
0))