module Main where import System.Posix.IO import qualified System.Posix.IO.Select as S import System.Posix.IO.Select.STM import qualified System.Posix.IO.Select.MVar as M import Control.Concurrent import Control.Concurrent.STM.TMVar import Control.Concurrent.STM flags :: OpenFileFlags flags = OpenFileFlags { append = False, exclusive = False, noctty = False, nonBlock = True, trunc = False } main :: IO () main = newEmptyTMVarIO >>= \t -> forkIO (interruptor t) >> putStrLn "The interruptor has been launched." >> openFd "fifo" ReadOnly Nothing flags >>= \fd -> openFd "fifo2" ReadOnly Nothing flags >>= \fd2 -> openFd "fifo3" ReadOnly Nothing flags >>= \fd3 -> openFd "fifo4" ReadOnly Nothing flags >>= \fd4 -> putStrLn "The file was opened, so let the waiting game begin!" >> selectOrTakeTMVar [fd,fd2,fd3,fd4] [] [] (Time 15 0) t >>= \ret -> case ret of Left 0 -> putStrLn "select() timed out on the files." Left x -> putStrLn "There's data in one of the files!" Right s -> putStrLn $ "Oh no, the interruptor is here: " ++ s interruptor :: TMVar String -> IO () interruptor t = threadDelay (10 * 1000000) >> atomically (putTMVar t "Bwahahaha, the interruptor was first!")