ports-0.4.3.1: The Haskell Ports LibrarySource codeContentsIndex
Control.Concurrent.Ports
Synopsis
type PortFilter a = a -> a -> Maybe a
type PortNotifier a = a -> IO ()
data Port a
withPorts :: [(String, IO ())] -> ([String] -> IO ()) -> IO ()
newPort :: a -> IO (Port a)
listenToNewPort :: a -> IO (Port a, [a])
newFilteringPort :: a -> PortFilter a -> IO (Port a)
newProxyPort :: a -> PortNotifier a -> IO (Port a, PortNotifier a)
openPort :: Port a -> IO ()
closePort :: Port a -> IO ()
isClosedPort :: Port a -> IO Bool
waitUntilClosedPort :: Port a -> IO ()
keepAlivePort :: Port a -> IO ()
setThreadInfo :: Port a -> ThreadId -> MVar () -> IO ()
waitForThread :: Port a -> IO ()
waitForPort :: Port a -> IO ()
waitForPortThread :: Port a -> IO ()
closeAndWaitForPort :: Port a -> IO ()
listenToPort :: Port a -> IO [a]
(<--) :: Port a -> a -> IO ()
(<==) :: Port a -> [a] -> IO ()
(<-$) :: Port a -> (a -> a) -> IO ()
chainPorts :: (a -> b) -> Port a -> Port b -> IO ()
linkPorts :: (a -> b) -> (b -> a) -> Port a -> Port b -> IO ()
(<->) :: Port a -> Port a -> IO ()
peekIntoPort :: Port a -> IO (Maybe a)
keepAliveForkIO :: IO () -> IO ThreadId
Documentation
type PortFilter a = a -> a -> Maybe aSource
type PortNotifier a = a -> IO ()Source
data Port a Source
withPorts :: [(String, IO ())] -> ([String] -> IO ()) -> IO ()Source
newPort :: a -> IO (Port a)Source
listenToNewPort :: a -> IO (Port a, [a])Source
newFilteringPort :: a -> PortFilter a -> IO (Port a)Source
newProxyPort :: a -> PortNotifier a -> IO (Port a, PortNotifier a)Source
openPort :: Port a -> IO ()Source

Open given port another time to allow for repeated closing.

FIXME: Should this better pass out a new port value? Then, closing that new port handle while not closing the whole port should invalidate that new handle. (Would probably, at least, be nicer for debugging.)

closePort :: Port a -> IO ()Source

Close a port.

  • If the port has been opened multiple times, it can be closed the corresponding number of times before it will be irrevocably shut, whereby creation of a port counts as one opening.
  • Closing an already closed port is a no-op.
isClosedPort :: Port a -> IO BoolSource

Check whether a given port is closed.

  • ATTENTION: This routine is a potential source of race conditions. Use with care. If this routine returns False, the state of the port may have changed by the time the return value is inspected.
waitUntilClosedPort :: Port a -> IO ()Source
keepAlivePort :: Port a -> IO ()Source
setThreadInfo :: Port a -> ThreadId -> MVar () -> IO ()Source

Associate a thread with a port

  • Sets the thread id and a synchronisation variable that will be set by the thread when it terminates
waitForThread :: Port a -> IO ()Source

Synchronise on the synchronisation variable in a port's thread info, which is set as soon as the thread terminates.

  • If a thread is associate with more than one port, waiting for any or all ports will have the same effect

FIXME: should we also wait until the port is closed? (if the thread traverses the whole port stream stream, it won't terminate until the port is closed anyway)

waitForPort :: Port a -> IO ()Source

Synchronise on a port being closed.

FIXME: It would be more efficient if a port would keep a list of threads to notify when a port is being closed.

waitForPortThread :: Port a -> IO ()Source
Wait until both the port is closed and the corresponding thread has terminated.
closeAndWaitForPort :: Port a -> IO ()Source
Ensure that the port is closed before waiting for the associated thread to terminate.
listenToPort :: Port a -> IO [a]Source
(<--) :: Port a -> a -> IO ()Source
(<==) :: Port a -> [a] -> IO ()Source
(<-$) :: Port a -> (a -> a) -> IO ()Source
chainPorts :: (a -> b) -> Port a -> Port b -> IO ()Source
linkPorts :: (a -> b) -> (b -> a) -> Port a -> Port b -> IO ()Source
(<->) :: Port a -> Port a -> IO ()Source
peekIntoPort :: Port a -> IO (Maybe a)Source
keepAliveForkIO :: IO () -> IO ThreadIdSource
Produced by Haddock version 2.6.0