module Blucontrol.Monad.ApplyValue.Print ( ApplyValuePrintT , runApplyValuePrintT ) where import Control.Monad.Base import Control.Monad.Trans import Control.Monad.Trans.Control import Control.Monad.Trans.Control.Default import Blucontrol.Monad.ApplyValue newtype ApplyValuePrintT c m a = ApplyValuePrintT { forall c (m :: * -> *) a. ApplyValuePrintT c m a -> m a unApplyValuePrintT :: m a } deriving (Functor (ApplyValuePrintT c m) Functor (ApplyValuePrintT c m) -> (forall a. a -> ApplyValuePrintT c m a) -> (forall a b. ApplyValuePrintT c m (a -> b) -> ApplyValuePrintT c m a -> ApplyValuePrintT c m b) -> (forall a b c. (a -> b -> c) -> ApplyValuePrintT c m a -> ApplyValuePrintT c m b -> ApplyValuePrintT c m c) -> (forall a b. ApplyValuePrintT c m a -> ApplyValuePrintT c m b -> ApplyValuePrintT c m b) -> (forall a b. ApplyValuePrintT c m a -> ApplyValuePrintT c m b -> ApplyValuePrintT c m a) -> Applicative (ApplyValuePrintT c m) forall a. a -> ApplyValuePrintT c m a forall a b. ApplyValuePrintT c m a -> ApplyValuePrintT c m b -> ApplyValuePrintT c m a forall a b. ApplyValuePrintT c m a -> ApplyValuePrintT c m b -> ApplyValuePrintT c m b forall a b. ApplyValuePrintT c m (a -> b) -> ApplyValuePrintT c m a -> ApplyValuePrintT c m b forall a b c. (a -> b -> c) -> ApplyValuePrintT c m a -> ApplyValuePrintT c m b -> ApplyValuePrintT c m c forall {c} {m :: * -> *}. Applicative m => Functor (ApplyValuePrintT c m) forall c (m :: * -> *) a. Applicative m => a -> ApplyValuePrintT c m a forall c (m :: * -> *) a b. Applicative m => ApplyValuePrintT c m a -> ApplyValuePrintT c m b -> ApplyValuePrintT c m a forall c (m :: * -> *) a b. Applicative m => ApplyValuePrintT c m a -> ApplyValuePrintT c m b -> ApplyValuePrintT c m b forall c (m :: * -> *) a b. Applicative m => ApplyValuePrintT c m (a -> b) -> ApplyValuePrintT c m a -> ApplyValuePrintT c m b forall c (m :: * -> *) a b c. Applicative m => (a -> b -> c) -> ApplyValuePrintT c m a -> ApplyValuePrintT c m b -> ApplyValuePrintT c m c forall (f :: * -> *). Functor f -> (forall a. a -> f a) -> (forall a b. f (a -> b) -> f a -> f b) -> (forall a b c. (a -> b -> c) -> f a -> f b -> f c) -> (forall a b. f a -> f b -> f b) -> (forall a b. f a -> f b -> f a) -> Applicative f $cpure :: forall c (m :: * -> *) a. Applicative m => a -> ApplyValuePrintT c m a pure :: forall a. a -> ApplyValuePrintT c m a $c<*> :: forall c (m :: * -> *) a b. Applicative m => ApplyValuePrintT c m (a -> b) -> ApplyValuePrintT c m a -> ApplyValuePrintT c m b <*> :: forall a b. ApplyValuePrintT c m (a -> b) -> ApplyValuePrintT c m a -> ApplyValuePrintT c m b $cliftA2 :: forall c (m :: * -> *) a b c. Applicative m => (a -> b -> c) -> ApplyValuePrintT c m a -> ApplyValuePrintT c m b -> ApplyValuePrintT c m c liftA2 :: forall a b c. (a -> b -> c) -> ApplyValuePrintT c m a -> ApplyValuePrintT c m b -> ApplyValuePrintT c m c $c*> :: forall c (m :: * -> *) a b. Applicative m => ApplyValuePrintT c m a -> ApplyValuePrintT c m b -> ApplyValuePrintT c m b *> :: forall a b. ApplyValuePrintT c m a -> ApplyValuePrintT c m b -> ApplyValuePrintT c m b $c<* :: forall c (m :: * -> *) a b. Applicative m => ApplyValuePrintT c m a -> ApplyValuePrintT c m b -> ApplyValuePrintT c m a <* :: forall a b. ApplyValuePrintT c m a -> ApplyValuePrintT c m b -> ApplyValuePrintT c m a Applicative, (forall a b. (a -> b) -> ApplyValuePrintT c m a -> ApplyValuePrintT c m b) -> (forall a b. a -> ApplyValuePrintT c m b -> ApplyValuePrintT c m a) -> Functor (ApplyValuePrintT c m) forall a b. a -> ApplyValuePrintT c m b -> ApplyValuePrintT c m a forall a b. (a -> b) -> ApplyValuePrintT c m a -> ApplyValuePrintT c m b forall c (m :: * -> *) a b. Functor m => a -> ApplyValuePrintT c m b -> ApplyValuePrintT c m a forall c (m :: * -> *) a b. Functor m => (a -> b) -> ApplyValuePrintT c m a -> ApplyValuePrintT c m b forall (f :: * -> *). (forall a b. (a -> b) -> f a -> f b) -> (forall a b. a -> f b -> f a) -> Functor f $cfmap :: forall c (m :: * -> *) a b. Functor m => (a -> b) -> ApplyValuePrintT c m a -> ApplyValuePrintT c m b fmap :: forall a b. (a -> b) -> ApplyValuePrintT c m a -> ApplyValuePrintT c m b $c<$ :: forall c (m :: * -> *) a b. Functor m => a -> ApplyValuePrintT c m b -> ApplyValuePrintT c m a <$ :: forall a b. a -> ApplyValuePrintT c m b -> ApplyValuePrintT c m a Functor, Applicative (ApplyValuePrintT c m) Applicative (ApplyValuePrintT c m) -> (forall a b. ApplyValuePrintT c m a -> (a -> ApplyValuePrintT c m b) -> ApplyValuePrintT c m b) -> (forall a b. ApplyValuePrintT c m a -> ApplyValuePrintT c m b -> ApplyValuePrintT c m b) -> (forall a. a -> ApplyValuePrintT c m a) -> Monad (ApplyValuePrintT c m) forall a. a -> ApplyValuePrintT c m a forall a b. ApplyValuePrintT c m a -> ApplyValuePrintT c m b -> ApplyValuePrintT c m b forall a b. ApplyValuePrintT c m a -> (a -> ApplyValuePrintT c m b) -> ApplyValuePrintT c m b forall {c} {m :: * -> *}. Monad m => Applicative (ApplyValuePrintT c m) forall c (m :: * -> *) a. Monad m => a -> ApplyValuePrintT c m a forall c (m :: * -> *) a b. Monad m => ApplyValuePrintT c m a -> ApplyValuePrintT c m b -> ApplyValuePrintT c m b forall c (m :: * -> *) a b. Monad m => ApplyValuePrintT c m a -> (a -> ApplyValuePrintT c m b) -> ApplyValuePrintT c m b forall (m :: * -> *). Applicative m -> (forall a b. m a -> (a -> m b) -> m b) -> (forall a b. m a -> m b -> m b) -> (forall a. a -> m a) -> Monad m $c>>= :: forall c (m :: * -> *) a b. Monad m => ApplyValuePrintT c m a -> (a -> ApplyValuePrintT c m b) -> ApplyValuePrintT c m b >>= :: forall a b. ApplyValuePrintT c m a -> (a -> ApplyValuePrintT c m b) -> ApplyValuePrintT c m b $c>> :: forall c (m :: * -> *) a b. Monad m => ApplyValuePrintT c m a -> ApplyValuePrintT c m b -> ApplyValuePrintT c m b >> :: forall a b. ApplyValuePrintT c m a -> ApplyValuePrintT c m b -> ApplyValuePrintT c m b $creturn :: forall c (m :: * -> *) a. Monad m => a -> ApplyValuePrintT c m a return :: forall a. a -> ApplyValuePrintT c m a Monad, MonadBase b, MonadBaseControl b) deriving ((forall (m :: * -> *) a. Monad m => m a -> ApplyValuePrintT c m a) -> MonadTrans (ApplyValuePrintT c) forall c (m :: * -> *) a. Monad m => m a -> ApplyValuePrintT c m a forall (m :: * -> *) a. Monad m => m a -> ApplyValuePrintT c m a forall (t :: (* -> *) -> * -> *). (forall (m :: * -> *) a. Monad m => m a -> t m a) -> MonadTrans t $clift :: forall c (m :: * -> *) a. Monad m => m a -> ApplyValuePrintT c m a lift :: forall (m :: * -> *) a. Monad m => m a -> ApplyValuePrintT c m a MonadTrans, MonadTrans (ApplyValuePrintT c) MonadTrans (ApplyValuePrintT c) -> (forall (m :: * -> *) a. Monad m => (Run (ApplyValuePrintT c) -> m a) -> ApplyValuePrintT c m a) -> (forall (m :: * -> *) a. Monad m => m (StT (ApplyValuePrintT c) a) -> ApplyValuePrintT c m a) -> MonadTransControl (ApplyValuePrintT c) forall c. MonadTrans (ApplyValuePrintT c) forall c (m :: * -> *) a. Monad m => m (StT (ApplyValuePrintT c) a) -> ApplyValuePrintT c m a forall c (m :: * -> *) a. Monad m => (Run (ApplyValuePrintT c) -> m a) -> ApplyValuePrintT c m a forall (m :: * -> *) a. Monad m => m (StT (ApplyValuePrintT c) a) -> ApplyValuePrintT c m a forall (m :: * -> *) a. Monad m => (Run (ApplyValuePrintT c) -> m a) -> ApplyValuePrintT c m a forall (t :: (* -> *) -> * -> *). MonadTrans t -> (forall (m :: * -> *) a. Monad m => (Run t -> m a) -> t m a) -> (forall (m :: * -> *) a. Monad m => m (StT t a) -> t m a) -> MonadTransControl t $cliftWith :: forall c (m :: * -> *) a. Monad m => (Run (ApplyValuePrintT c) -> m a) -> ApplyValuePrintT c m a liftWith :: forall (m :: * -> *) a. Monad m => (Run (ApplyValuePrintT c) -> m a) -> ApplyValuePrintT c m a $crestoreT :: forall c (m :: * -> *) a. Monad m => m (StT (ApplyValuePrintT c) a) -> ApplyValuePrintT c m a restoreT :: forall (m :: * -> *) a. Monad m => m (StT (ApplyValuePrintT c) a) -> ApplyValuePrintT c m a MonadTransControl) via Stack0T instance (MonadBaseControl IO m, Show c) => MonadApplyValue (ApplyValuePrintT c m) where type ApplicableValue (ApplyValuePrintT c m) = c applyValue :: ApplicableValue (ApplyValuePrintT c m) -> ApplyValuePrintT c m () applyValue = IO () -> ApplyValuePrintT c m () forall α. IO α -> ApplyValuePrintT c m α forall (b :: * -> *) (m :: * -> *) α. MonadBase b m => b α -> m α liftBase (IO () -> ApplyValuePrintT c m ()) -> (c -> IO ()) -> c -> ApplyValuePrintT c m () forall b c a. (b -> c) -> (a -> b) -> a -> c . c -> IO () forall a. Show a => a -> IO () print runApplyValuePrintT :: ApplyValuePrintT c m a -> m a runApplyValuePrintT :: forall c (m :: * -> *) a. ApplyValuePrintT c m a -> m a runApplyValuePrintT = ApplyValuePrintT c m a -> m a forall c (m :: * -> *) a. ApplyValuePrintT c m a -> m a unApplyValuePrintT