{-# OPTIONS_GHC -Wall #-}
----------------------------------------------------------------------
-- |
-- Module      :  FRP.Reactive.Internal.IVar
-- Copyright   :  (c) Conal Elliott 2008
-- License     :  BSD3
-- 
-- Maintainer  :  conal@conal.net
-- Stability   :  experimental
-- 
-- Write-once variables.
----------------------------------------------------------------------

module FRP.Reactive.Internal.IVar 
    ( IVar, newEmptyIVar, readIVar, tryReadIVar, writeIVar )
where

import Control.Concurrent.MVar
import Control.Applicative ((<$>))
import System.IO.Unsafe (unsafePerformIO)

newtype IVar a = IVar (MVar a)

newEmptyIVar :: IO (IVar a)
newEmptyIVar = IVar <$> newEmptyMVar

-- | Returns the value in the IVar.  The *value* will block
-- until the variable becomes filled.
readIVar :: IVar a -> a
readIVar (IVar v) = unsafePerformIO $ readMVar v

-- | Returns Nothing if the IVar has no value yet, otherwise
-- returns the value.
tryReadIVar :: IVar a -> IO (Maybe a)
tryReadIVar (IVar v) = do
    empty <- isEmptyMVar v
    if empty
       then return Nothing
       else Just <$> readMVar v

-- | Puts the value of the IVar.  If it already has a value,
-- block forever.
writeIVar :: IVar a -> a -> IO ()
writeIVar (IVar v) x = putMVar v x