-- | Haskell Ports Library: ports consumed in a specific thread
--
--  Author : Manuel M T Chakravarty
--  Created: 18 June 2003
--
--  Version $Revision: 1.1 $ from $Date: 2003/06/22 15:25:32 $
--
--  Copyright (c) 2003 Manuel M T Chakravarty
--
--  This library is free software; you can redistribute it and/or
--  modify it under the terms of the GNU Library General Public
--  License as published by the Free Software Foundation; either
--  version 2 of the License, or (at your option) any later version.
--
--  This library is distributed in the hope that it will be useful,
--  but WITHOUT ANY WARRANTY; without even the implied warranty of
--  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
--  Library General Public License for more details.
--
--- Description ---------------------------------------------------------------
--
--  Language: Haskell 98
--
--  This modules associates a message consuming thread with any newly created
--  port.
--
--- Todo ----------------------------------------------------------------------
--
--  * We might want to the merge consuming thread's ThreadId and the port into
--    one abstract value, which the thread can obtain with a function `self ::
--    IO (Port a)'.
--
--  * Would it be worthwhile to have an Erlang-ish variant, where a thread is
--    associated with only one port and instead of getting a stream of port
--    values as an argument, the thread can use a receive-like IO-function
--    (including support for timeouts). 

module Control.Concurrent.PortThreads (
  spawn, spawn_, spawn2, spawn2_
) where

import Control.Concurrent
  (forkIO, newEmptyMVar, putMVar)
import Control.Exception
  (finally)

import Control.Concurrent.Ports (Port, listenToNewPort, setThreadInfo)


-- |Fork a thread listening to a newly generated port
--
--FIXME: should this be called `newPort'?
spawn :: a -> ([a] -> IO ()) -> IO (Port a)
spawn x m =
  do
    (p, stream) <- listenToNewPort x
    sv <- newEmptyMVar
    tid <- forkIO $ m stream `finally` putMVar sv ()
    setThreadInfo p tid sv
    return p

spawn_ :: ([a] -> IO ()) -> IO (Port a)
spawn_ = spawn undefined

spawn2 :: a -> b -> ([a] -> [b] -> IO ()) -> IO (Port a, Port b)
spawn2 x y m =
  do
    (px, streamx) <- listenToNewPort x
    (py, streamy) <- listenToNewPort y
    sv <- newEmptyMVar
    tid <- forkIO $ m streamx streamy `finally` putMVar sv ()
    setThreadInfo px tid sv
    setThreadInfo py tid sv
    return (px, py)

spawn2_ :: ([a] -> [b] -> IO ()) -> IO (Port a, Port b)
spawn2_ = spawn2 undefined undefined

-- FIXME: Seems to be a family of spawn functions whose arity depends on the
--   number of port inputs to the listener.  Is there a more general way of
--   defining this?