{-# LANGUAGE CPP #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE UndecidableInstances #-}
#ifdef USE_REFLEX_OPTIMIZER
{-# OPTIONS_GHC -fplugin=Reflex.Optimizer #-}
#endif
module Reflex.BehaviorWriter.Class
( MonadBehaviorWriter
, BehaviorWriter(..)
) where
import Control.Monad.Reader (ReaderT, lift)
import Reflex.Class (Behavior)
{-# DEPRECATED MonadBehaviorWriter "Use 'BehaviorWriter' instead" #-}
type MonadBehaviorWriter = BehaviorWriter
class (Monad m, Monoid w) => BehaviorWriter t w m | m -> t w where
tellBehavior :: Behavior t w -> m ()
instance BehaviorWriter t w m => BehaviorWriter t w (ReaderT r m) where
tellBehavior :: Behavior t w -> ReaderT r m ()
tellBehavior = m () -> ReaderT r m ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m () -> ReaderT r m ())
-> (Behavior t w -> m ()) -> Behavior t w -> ReaderT r m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Behavior t w -> m ()
forall t w (m :: * -> *).
BehaviorWriter t w m =>
Behavior t w -> m ()
tellBehavior