module SocketActivation.GetSockets where import Control.Monad (Monad ((>>=))) import Control.Monad.IO.Class (MonadIO (liftIO)) import Data.Either (Either) import Data.Function ((.)) import Data.Traversable (Traversable (traverse)) import System.IO (IO) import qualified Network.Socket as Net import SocketActivation.Concepts import SocketActivation.GetFileDescriptors import SocketActivation.IO getSocketList :: IO (Either Error [Socket]) getSocketList :: IO (Either Error [Socket]) getSocketList = IO' [Socket] -> IO (Either Error [Socket]) forall a. IO' a -> IO (Either Error a) run (IO' [Fd] getFds IO' [Fd] -> ([Fd] -> IO' [Socket]) -> IO' [Socket] forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b >>= [Fd] -> IO' [Socket] convertToSockets) where getFds :: IO' [Fd] getFds = IO (Either Error [Fd]) -> IO' [Fd] forall a. IO (Either Error a) -> IO' a IO' IO (Either Error [Fd]) getFileDescriptorList convertToSockets :: [Fd] -> IO' [Socket] convertToSockets = (Fd -> IO' Socket) -> [Fd] -> IO' [Socket] forall (t :: * -> *) (f :: * -> *) a b. (Traversable t, Applicative f) => (a -> f b) -> t a -> f (t b) traverse (IO Socket -> IO' Socket forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO Socket -> IO' Socket) -> (Fd -> IO Socket) -> Fd -> IO' Socket forall b c a. (b -> c) -> (a -> b) -> a -> c . Fd -> IO Socket fdSocket) fdSocket :: Fd -> IO Socket fdSocket :: Fd -> IO Socket fdSocket (Fd CInt i) = CInt -> IO Socket Net.mkSocket CInt i