module Reactive.Banana.Prim.Types where
import Control.Monad.Trans.RWSIO
import Control.Monad.Trans.Reader
import Control.Monad.Trans.ReaderWriterIO
import Data.Functor
import Data.Hashable
import Data.Monoid
import qualified Data.Vault.Lazy as Lazy
import System.IO.Unsafe
import System.Mem.Weak
import Reactive.Banana.Prim.Graph (Graph)
import Reactive.Banana.Prim.OrderedBag as OB (OrderedBag, empty)
import Reactive.Banana.Prim.Util
data Network = Network
{ nTime :: !Time
, nOutputs :: !(OrderedBag Output)
, nAlwaysP :: !(Maybe (Pulse ()))
}
type Inputs = ([SomeNode], Lazy.Vault)
type EvalNetwork a = Network -> IO (a, Network)
type Step = EvalNetwork (IO ())
emptyNetwork = Network
{ nTime = next beginning
, nOutputs = OB.empty
, nAlwaysP = Nothing
}
type Build = ReaderWriterIOT BuildR BuildW IO
type BuildR = (Time, Pulse ())
newtype BuildW = BuildW (DependencyBuilder, [Output], Action, Maybe (Build ()))
instance Monoid BuildW where
mempty = BuildW mempty
(BuildW x) `mappend` (BuildW y) = BuildW (x `mappend` y)
type BuildIO = Build
type DependencyBuilder = (Endo (Graph SomeNode), [(SomeNode, SomeNode)])
type Level = Int
ground :: Level
ground = 0
newtype Action = Action { doit :: IO () }
instance Monoid Action where
mempty = Action $ return ()
(Action x) `mappend` (Action y) = Action (x >> y)
data Lens s a = Lens (s -> a) (a -> s -> s)
set (Lens _ set) = set
update (Lens get set) f = \s -> set (f $ get s) s
type Pulse a = Ref (Pulse' a)
data Pulse' a = Pulse
{ _keyP :: Lazy.Key (Maybe a)
, _seenP :: !Time
, _evalP :: EvalP (Maybe a)
, _childrenP :: [Weak SomeNode]
, _parentsP :: [Weak SomeNode]
, _levelP :: !Level
, _nameP :: String
}
instance Show (Pulse a) where
show p = _nameP (unsafePerformIO $ readRef p) ++ " " ++ show (hashWithSalt 0 p)
type Latch a = Ref (Latch' a)
data Latch' a = Latch
{ _seenL :: !Time
, _valueL :: a
, _evalL :: EvalL a
}
type LatchWrite = Ref LatchWrite'
data LatchWrite' = forall a. LatchWrite
{ _evalLW :: EvalP a
, _latchLW :: Weak (Latch a)
}
type Output = Ref Output'
data Output' = Output
{ _evalO :: EvalP EvalO
}
instance Eq Output where (==) = equalRef
data SomeNode
= forall a. P (Pulse a)
| L LatchWrite
| O Output
instance Hashable SomeNode where
hashWithSalt s (P x) = hashWithSalt s x
hashWithSalt s (L x) = hashWithSalt s x
hashWithSalt s (O x) = hashWithSalt s x
instance Eq SomeNode where
(P x) == (P y) = equalRef x y
(L x) == (L y) = equalRef x y
(O x) == (O y) = equalRef x y
mkWeakNodeValue :: SomeNode -> v -> IO (Weak v)
mkWeakNodeValue (P x) = mkWeakRefValue x
mkWeakNodeValue (L x) = mkWeakRefValue x
mkWeakNodeValue (O x) = mkWeakRefValue x
seenP = Lens _seenP (\a s -> s { _seenP = a })
seenL = Lens _seenL (\a s -> s { _seenL = a })
valueL = Lens _valueL (\a s -> s { _valueL = a })
parentsP = Lens _parentsP (\a s -> s { _parentsP = a })
childrenP = Lens _childrenP (\a s -> s { _childrenP = a })
levelP = Lens _levelP (\a s -> s { _levelP = a })
type EvalPW = (EvalLW, [(Output, EvalO)])
type EvalLW = Action
type EvalO = Future (IO ())
type Future = IO
type EvalP = RWSIOT BuildR (EvalPW,BuildW) Lazy.Vault IO
type EvalL = ReaderWriterIOT () Time IO
printNode :: SomeNode -> IO String
printNode (P p) = _nameP <$> readRef p
printNode (L l) = return "L"
printNode (O o) = return "O"
newtype Time = T Integer deriving (Eq, Ord, Show, Read)
agesAgo :: Time
agesAgo = T (1)
beginning :: Time
beginning = T 0
next :: Time -> Time
next (T n) = T (n+1)
instance Monoid Time where
mappend (T x) (T y) = T (max x y)
mempty = beginning