module Main where import System.Posix.IO import System.Posix.IO.Select.FdSet.Unsafe import System.Posix.IO.Select import System.Posix.IO.Select.Types import System.Posix.Types import Control.Concurrent import Control.Concurrent.STM.OrElseIO import Control.Concurrent.STM import Control.Concurrent.STM.TMVar import Control.Concurrent.STM.TChan 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." >> newTChanIO >>= \c -> forkIO (interruptor2 c) >> putStrLn "The TChan 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!" >> runOrElse (select' [fd,fd2,fd3,fd4] [] [] (finite 5 0)) (readTChan c) >>= \ret -> case ret of Left x -> putStrLn ("select() returned: " ++ show x) 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!") interruptor2 :: TChan String -> IO () interruptor2 c = threadDelay (15 * 1000000) >> atomically (writeTChan c "Bwhaha, TChan interruptor was first!")