module Z.IO.UV.UVStream
(
initUVStream
, UVStream(..)
, getUVStreamFD
, closeUVStream
, helloWorld, echo
) where
import Control.Concurrent
import Control.Monad
import qualified Z.Data.Text.ShowT as T
import Z.IO.UV.Errno
import Z.IO.UV.FFI
import Z.IO.UV.Manager
import Z.IO.Buffered
import Z.IO.Exception
import Z.IO.Resource
import Data.IORef
import GHC.Ptr
data UVStream = UVStream
{ UVStream -> Ptr UVHandle
uvsHandle :: {-# UNPACK #-} !(Ptr UVHandle)
, UVStream -> UVSlot
uvsSlot :: {-# UNPACK #-} !UVSlot
, UVStream -> UVManager
uvsManager :: UVManager
, UVStream -> IORef Bool
uvsClosed :: {-# UNPACK #-} !(IORef Bool)
}
instance Show UVStream where show :: UVStream -> String
show = UVStream -> String
forall a. ShowT a => a -> String
T.toString
instance T.ShowT UVStream where
toUTF8BuilderP :: UVSlot -> UVStream -> Builder ()
toUTF8BuilderP UVSlot
_ (UVStream Ptr UVHandle
hdl UVSlot
slot UVManager
uvm IORef Bool
_) = do
Builder ()
"UVStream{uvsHandle=" Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Ptr UVHandle -> Builder ()
forall a. ShowT a => a -> Builder ()
T.toUTF8Builder Ptr UVHandle
hdl
Builder ()
",uvsSlot=" Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> UVSlot -> Builder ()
forall a. ShowT a => a -> Builder ()
T.toUTF8Builder UVSlot
slot
Builder ()
",uvsManager=" Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> UVManager -> Builder ()
forall a. ShowT a => a -> Builder ()
T.toUTF8Builder UVManager
uvm
Char -> Builder ()
T.char7 Char
'}'
initUVStream :: HasCallStack
=> (Ptr UVLoop -> Ptr UVHandle -> IO ())
-> UVManager
-> Resource UVStream
initUVStream :: (Ptr UVLoop -> Ptr UVHandle -> IO ())
-> UVManager -> Resource UVStream
initUVStream Ptr UVLoop -> Ptr UVHandle -> IO ()
f UVManager
uvm = IO UVStream -> (UVStream -> IO ()) -> Resource UVStream
forall a. IO a -> (a -> IO ()) -> Resource a
initResource
(UVManager -> (Ptr UVLoop -> IO UVStream) -> IO UVStream
forall a. HasCallStack => UVManager -> (Ptr UVLoop -> IO a) -> IO a
withUVManager UVManager
uvm ((Ptr UVLoop -> IO UVStream) -> IO UVStream)
-> (Ptr UVLoop -> IO UVStream) -> IO UVStream
forall a b. (a -> b) -> a -> b
$ \ Ptr UVLoop
loop -> do
Ptr UVHandle
hdl <- Ptr UVLoop -> IO (Ptr UVHandle)
hs_uv_handle_alloc Ptr UVLoop
loop
UVSlot
slot <- HasCallStack => UVManager -> IO UVSlotUnsafe -> IO UVSlot
UVManager -> IO UVSlotUnsafe -> IO UVSlot
getUVSlot UVManager
uvm (Ptr UVHandle -> IO UVSlotUnsafe
peekUVHandleData Ptr UVHandle
hdl)
Maybe UVSlot
_ <- MVar UVSlot -> IO (Maybe UVSlot)
forall a. MVar a -> IO (Maybe a)
tryTakeMVar (MVar UVSlot -> IO (Maybe UVSlot))
-> IO (MVar UVSlot) -> IO (Maybe UVSlot)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< UVManager -> UVSlot -> IO (MVar UVSlot)
getBlockMVar UVManager
uvm UVSlot
slot
Ptr UVLoop -> Ptr UVHandle -> IO ()
f Ptr UVLoop
loop Ptr UVHandle
hdl
IORef Bool
closed <- Bool -> IO (IORef Bool)
forall a. a -> IO (IORef a)
newIORef Bool
False
UVStream -> IO UVStream
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr UVHandle -> UVSlot -> UVManager -> IORef Bool -> UVStream
UVStream Ptr UVHandle
hdl UVSlot
slot UVManager
uvm IORef Bool
closed))
UVStream -> IO ()
closeUVStream
closeUVStream :: UVStream -> IO ()
closeUVStream :: UVStream -> IO ()
closeUVStream (UVStream Ptr UVHandle
hdl UVSlot
_ UVManager
uvm IORef Bool
closed) = UVManager -> IO () -> IO ()
forall a. HasCallStack => UVManager -> IO a -> IO a
withUVManager' UVManager
uvm (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
Bool
c <- IORef Bool -> IO Bool
forall a. IORef a -> IO a
readIORef IORef Bool
closed
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless Bool
c (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ IORef Bool -> Bool -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef Bool
closed Bool
True IO () -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Ptr UVHandle -> IO ()
hs_uv_handle_close Ptr UVHandle
hdl
getUVStreamFD :: HasCallStack => UVStream -> IO FD
getUVStreamFD :: UVStream -> IO FD
getUVStreamFD (UVStream Ptr UVHandle
hdl UVSlot
_ UVManager
_ IORef Bool
closed) = do
Bool
c <- IORef Bool -> IO Bool
forall a. IORef a -> IO a
readIORef IORef Bool
closed
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
c IO ()
forall a. HasCallStack => IO a
throwECLOSED
IO FD -> IO FD
forall a. (HasCallStack, Integral a) => IO a -> IO a
throwUVIfMinus (Ptr UVHandle -> IO FD
hs_uv_fileno Ptr UVHandle
hdl)
instance Input UVStream where
{-# INLINABLE readInput #-}
readInput :: UVStream -> Ptr Word8 -> UVSlot -> IO UVSlot
readInput (UVStream Ptr UVHandle
hdl UVSlot
slot UVManager
uvm IORef Bool
closed) Ptr Word8
buf UVSlot
len = IO UVSlot -> IO UVSlot
forall a. IO a -> IO a
mask_ (IO UVSlot -> IO UVSlot) -> IO UVSlot -> IO UVSlot
forall a b. (a -> b) -> a -> b
$ do
Bool
c <- IORef Bool -> IO Bool
forall a. IORef a -> IO a
readIORef IORef Bool
closed
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
c IO ()
forall a. HasCallStack => IO a
throwECLOSED
UVManager -> UVSlot -> Ptr Word8 -> UVSlot -> IO ()
pokeBufferTable UVManager
uvm UVSlot
slot Ptr Word8
buf UVSlot
len
MVar UVSlot
m <- UVManager -> UVSlot -> IO (MVar UVSlot)
getBlockMVar UVManager
uvm UVSlot
slot
Maybe UVSlot
_ <- MVar UVSlot -> IO (Maybe UVSlot)
forall a. MVar a -> IO (Maybe a)
tryTakeMVar MVar UVSlot
m
IO FD -> IO ()
forall a. (HasCallStack, Integral a) => IO a -> IO ()
throwUVIfMinus_ (IO FD -> IO ()) -> IO FD -> IO ()
forall a b. (a -> b) -> a -> b
$ UVManager -> IO FD -> IO FD
forall a. HasCallStack => UVManager -> IO a -> IO a
withUVManager' UVManager
uvm (Ptr UVHandle -> IO FD
hs_uv_read_start Ptr UVHandle
hdl)
UVSlot
r <- MVar UVSlot -> IO UVSlot
forall a. MVar a -> IO a
takeMVar MVar UVSlot
m IO UVSlot -> IO () -> IO UVSlot
forall a b. IO a -> IO b -> IO a
`onException` (do
FD
_ <- UVManager -> IO FD -> IO FD
forall a. HasCallStack => UVManager -> IO a -> IO a
withUVManager' UVManager
uvm (Ptr UVHandle -> IO FD
uv_read_stop Ptr UVHandle
hdl)
IO (Maybe UVSlot) -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (MVar UVSlot -> IO (Maybe UVSlot)
forall a. MVar a -> IO (Maybe a)
tryTakeMVar MVar UVSlot
m))
if | UVSlot
r UVSlot -> UVSlot -> Bool
forall a. Ord a => a -> a -> Bool
> UVSlot
0 -> UVSlot -> IO UVSlot
forall (m :: * -> *) a. Monad m => a -> m a
return UVSlot
r
| UVSlot
r UVSlot -> UVSlot -> Bool
forall a. Eq a => a -> a -> Bool
== FD -> UVSlot
forall a b. (Integral a, Num b) => a -> b
fromIntegral FD
UV_EOF -> UVSlot -> IO UVSlot
forall (m :: * -> *) a. Monad m => a -> m a
return UVSlot
0
| UVSlot
r UVSlot -> UVSlot -> Bool
forall a. Ord a => a -> a -> Bool
< UVSlot
0 -> IO UVSlot -> IO UVSlot
forall a. (HasCallStack, Integral a) => IO a -> IO a
throwUVIfMinus (UVSlot -> IO UVSlot
forall (m :: * -> *) a. Monad m => a -> m a
return UVSlot
r)
| Bool
otherwise -> FD -> IOEInfo -> IO UVSlot
forall a. FD -> IOEInfo -> IO a
throwUVError FD
UV_UNKNOWN IOEInfo :: Text -> Text -> CallStack -> IOEInfo
IOEInfo{
ioeName :: Text
ioeName = Text
"UVStream read error"
, ioeDescription :: Text
ioeDescription = Text
"UVStream read should never return 0 before EOF"
, ioeCallStack :: CallStack
ioeCallStack = CallStack
HasCallStack => CallStack
callStack
}
instance Output UVStream where
{-# INLINABLE writeOutput #-}
writeOutput :: UVStream -> Ptr Word8 -> UVSlot -> IO ()
writeOutput (UVStream Ptr UVHandle
hdl UVSlot
_ UVManager
uvm IORef Bool
closed) Ptr Word8
buf UVSlot
len = IO () -> IO ()
forall a. IO a -> IO a
mask_ (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
Bool
c <- IORef Bool -> IO Bool
forall a. IORef a -> IO a
readIORef IORef Bool
closed
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
c IO ()
forall a. HasCallStack => IO a
throwECLOSED
MVar UVSlot
m <- UVManager -> IO (MVar UVSlot) -> IO (MVar UVSlot)
forall a. HasCallStack => UVManager -> IO a -> IO a
withUVManager' UVManager
uvm (IO (MVar UVSlot) -> IO (MVar UVSlot))
-> IO (MVar UVSlot) -> IO (MVar UVSlot)
forall a b. (a -> b) -> a -> b
$ do
UVSlot
reqSlot <- HasCallStack => UVManager -> IO UVSlotUnsafe -> IO UVSlot
UVManager -> IO UVSlotUnsafe -> IO UVSlot
getUVSlot UVManager
uvm (Ptr UVHandle -> Ptr Word8 -> UVSlot -> IO UVSlotUnsafe
hs_uv_write Ptr UVHandle
hdl Ptr Word8
buf UVSlot
len)
MVar UVSlot
m <- UVManager -> UVSlot -> IO (MVar UVSlot)
getBlockMVar UVManager
uvm UVSlot
reqSlot
Maybe UVSlot
_ <- MVar UVSlot -> IO (Maybe UVSlot)
forall a. MVar a -> IO (Maybe a)
tryTakeMVar MVar UVSlot
m
MVar UVSlot -> IO (MVar UVSlot)
forall (m :: * -> *) a. Monad m => a -> m a
return MVar UVSlot
m
IO UVSlot -> IO ()
forall a. (HasCallStack, Integral a) => IO a -> IO ()
throwUVIfMinus_ (IO UVSlot -> IO UVSlot
forall a. IO a -> IO a
uninterruptibleMask_ (IO UVSlot -> IO UVSlot) -> IO UVSlot -> IO UVSlot
forall a b. (a -> b) -> a -> b
$ MVar UVSlot -> IO UVSlot
forall a. MVar a -> IO a
takeMVar MVar UVSlot
m)
helloWorld :: UVStream -> IO ()
helloWorld :: UVStream -> IO ()
helloWorld UVStream
uvs = UVStream -> Ptr Word8 -> UVSlot -> IO ()
forall o.
(Output o, HasCallStack) =>
o -> Ptr Word8 -> UVSlot -> IO ()
writeOutput UVStream
uvs (Addr# -> Ptr Word8
forall a. Addr# -> Ptr a
Ptr Addr#
"hello world"#) UVSlot
11
echo :: UVStream -> IO ()
echo :: UVStream -> IO ()
echo UVStream
uvs = do
BufferedInput
i <- UVStream -> IO BufferedInput
forall i. Input i => i -> IO BufferedInput
newBufferedInput UVStream
uvs
BufferedOutput
o <- UVStream -> IO BufferedOutput
forall o. Output o => o -> IO BufferedOutput
newBufferedOutput UVStream
uvs
IO () -> IO ()
forall (f :: * -> *) a b. Applicative f => f a -> f b
forever (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ HasCallStack => BufferedInput -> IO Bytes
BufferedInput -> IO Bytes
readBuffer BufferedInput
i IO Bytes -> (Bytes -> IO ()) -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= HasCallStack => BufferedOutput -> Bytes -> IO ()
BufferedOutput -> Bytes -> IO ()
writeBuffer BufferedOutput
o IO () -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> HasCallStack => BufferedOutput -> IO ()
BufferedOutput -> IO ()
flushBuffer BufferedOutput
o