module SocketActivation.GetSockets where import Essentials import Control.Monad.IO.Class (MonadIO (liftIO)) import Data.Either (Either) import System.IO (IO) import qualified Network.Socket as Net import SocketActivation.Concepts (Socket, Fd (..), Error) import SocketActivation.GetFileDescriptors (getFileDescriptorList) import SocketActivation.IO (IO' (IO', run)) 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' [Socket] -> IO (Either Error [Socket])) -> IO' [Socket] -> IO (Either Error [Socket]) forall a b. (a -> b) -> a -> b $ IO (Either Error [Fd]) -> IO' [Fd] forall a. IO (Either Error a) -> IO' a IO' IO (Either Error [Fd]) getFileDescriptorList IO' [Fd] -> ([Fd] -> IO' [Socket]) -> IO' [Socket] forall a b. IO' a -> (a -> IO' b) -> IO' b forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b >>= (Fd -> IO' Socket) -> [Fd] -> IO' [Socket] forall (t :: * -> *) (f :: * -> *) a b. (Traversable t, Applicative f) => (a -> f b) -> t a -> f (t b) forall (f :: * -> *) a b. Applicative f => (a -> f b) -> [a] -> f [b] traverse (IO Socket -> IO' Socket forall a. IO a -> IO' a 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 forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat 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