{-# LANGUAGE UndecidableInstances #-} module Blucontrol.Recolor.Print ( RecolorPrintT , runRecolorPrintT ) where import Control.Monad.Base import Control.Monad.Trans import Control.Monad.Trans.Control import Blucontrol.Recolor newtype RecolorPrintT m a = RecolorPrintT { RecolorPrintT m a -> m a unRecolorPrintT :: m a } deriving (Functor (RecolorPrintT m) a -> RecolorPrintT m a Functor (RecolorPrintT m) -> (forall a. a -> RecolorPrintT m a) -> (forall a b. RecolorPrintT m (a -> b) -> RecolorPrintT m a -> RecolorPrintT m b) -> (forall a b c. (a -> b -> c) -> RecolorPrintT m a -> RecolorPrintT m b -> RecolorPrintT m c) -> (forall a b. RecolorPrintT m a -> RecolorPrintT m b -> RecolorPrintT m b) -> (forall a b. RecolorPrintT m a -> RecolorPrintT m b -> RecolorPrintT m a) -> Applicative (RecolorPrintT m) RecolorPrintT m a -> RecolorPrintT m b -> RecolorPrintT m b RecolorPrintT m a -> RecolorPrintT m b -> RecolorPrintT m a RecolorPrintT m (a -> b) -> RecolorPrintT m a -> RecolorPrintT m b (a -> b -> c) -> RecolorPrintT m a -> RecolorPrintT m b -> RecolorPrintT m c forall a. a -> RecolorPrintT m a forall a b. RecolorPrintT m a -> RecolorPrintT m b -> RecolorPrintT m a forall a b. RecolorPrintT m a -> RecolorPrintT m b -> RecolorPrintT m b forall a b. RecolorPrintT m (a -> b) -> RecolorPrintT m a -> RecolorPrintT m b forall a b c. (a -> b -> c) -> RecolorPrintT m a -> RecolorPrintT m b -> RecolorPrintT 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 forall (m :: * -> *). Applicative m => Functor (RecolorPrintT m) forall (m :: * -> *) a. Applicative m => a -> RecolorPrintT m a forall (m :: * -> *) a b. Applicative m => RecolorPrintT m a -> RecolorPrintT m b -> RecolorPrintT m a forall (m :: * -> *) a b. Applicative m => RecolorPrintT m a -> RecolorPrintT m b -> RecolorPrintT m b forall (m :: * -> *) a b. Applicative m => RecolorPrintT m (a -> b) -> RecolorPrintT m a -> RecolorPrintT m b forall (m :: * -> *) a b c. Applicative m => (a -> b -> c) -> RecolorPrintT m a -> RecolorPrintT m b -> RecolorPrintT m c <* :: RecolorPrintT m a -> RecolorPrintT m b -> RecolorPrintT m a $c<* :: forall (m :: * -> *) a b. Applicative m => RecolorPrintT m a -> RecolorPrintT m b -> RecolorPrintT m a *> :: RecolorPrintT m a -> RecolorPrintT m b -> RecolorPrintT m b $c*> :: forall (m :: * -> *) a b. Applicative m => RecolorPrintT m a -> RecolorPrintT m b -> RecolorPrintT m b liftA2 :: (a -> b -> c) -> RecolorPrintT m a -> RecolorPrintT m b -> RecolorPrintT m c $cliftA2 :: forall (m :: * -> *) a b c. Applicative m => (a -> b -> c) -> RecolorPrintT m a -> RecolorPrintT m b -> RecolorPrintT m c <*> :: RecolorPrintT m (a -> b) -> RecolorPrintT m a -> RecolorPrintT m b $c<*> :: forall (m :: * -> *) a b. Applicative m => RecolorPrintT m (a -> b) -> RecolorPrintT m a -> RecolorPrintT m b pure :: a -> RecolorPrintT m a $cpure :: forall (m :: * -> *) a. Applicative m => a -> RecolorPrintT m a $cp1Applicative :: forall (m :: * -> *). Applicative m => Functor (RecolorPrintT m) Applicative, a -> RecolorPrintT m b -> RecolorPrintT m a (a -> b) -> RecolorPrintT m a -> RecolorPrintT m b (forall a b. (a -> b) -> RecolorPrintT m a -> RecolorPrintT m b) -> (forall a b. a -> RecolorPrintT m b -> RecolorPrintT m a) -> Functor (RecolorPrintT m) forall a b. a -> RecolorPrintT m b -> RecolorPrintT m a forall a b. (a -> b) -> RecolorPrintT m a -> RecolorPrintT m b forall (m :: * -> *) a b. Functor m => a -> RecolorPrintT m b -> RecolorPrintT m a forall (m :: * -> *) a b. Functor m => (a -> b) -> RecolorPrintT m a -> RecolorPrintT m b forall (f :: * -> *). (forall a b. (a -> b) -> f a -> f b) -> (forall a b. a -> f b -> f a) -> Functor f <$ :: a -> RecolorPrintT m b -> RecolorPrintT m a $c<$ :: forall (m :: * -> *) a b. Functor m => a -> RecolorPrintT m b -> RecolorPrintT m a fmap :: (a -> b) -> RecolorPrintT m a -> RecolorPrintT m b $cfmap :: forall (m :: * -> *) a b. Functor m => (a -> b) -> RecolorPrintT m a -> RecolorPrintT m b Functor, Applicative (RecolorPrintT m) a -> RecolorPrintT m a Applicative (RecolorPrintT m) -> (forall a b. RecolorPrintT m a -> (a -> RecolorPrintT m b) -> RecolorPrintT m b) -> (forall a b. RecolorPrintT m a -> RecolorPrintT m b -> RecolorPrintT m b) -> (forall a. a -> RecolorPrintT m a) -> Monad (RecolorPrintT m) RecolorPrintT m a -> (a -> RecolorPrintT m b) -> RecolorPrintT m b RecolorPrintT m a -> RecolorPrintT m b -> RecolorPrintT m b forall a. a -> RecolorPrintT m a forall a b. RecolorPrintT m a -> RecolorPrintT m b -> RecolorPrintT m b forall a b. RecolorPrintT m a -> (a -> RecolorPrintT m b) -> RecolorPrintT m b forall (m :: * -> *). Monad m => Applicative (RecolorPrintT m) forall (m :: * -> *) a. Monad m => a -> RecolorPrintT m a forall (m :: * -> *) a b. Monad m => RecolorPrintT m a -> RecolorPrintT m b -> RecolorPrintT m b forall (m :: * -> *) a b. Monad m => RecolorPrintT m a -> (a -> RecolorPrintT m b) -> RecolorPrintT 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 return :: a -> RecolorPrintT m a $creturn :: forall (m :: * -> *) a. Monad m => a -> RecolorPrintT m a >> :: RecolorPrintT m a -> RecolorPrintT m b -> RecolorPrintT m b $c>> :: forall (m :: * -> *) a b. Monad m => RecolorPrintT m a -> RecolorPrintT m b -> RecolorPrintT m b >>= :: RecolorPrintT m a -> (a -> RecolorPrintT m b) -> RecolorPrintT m b $c>>= :: forall (m :: * -> *) a b. Monad m => RecolorPrintT m a -> (a -> RecolorPrintT m b) -> RecolorPrintT m b $cp1Monad :: forall (m :: * -> *). Monad m => Applicative (RecolorPrintT m) Monad, MonadBase b, MonadBaseControl b) instance MonadTrans RecolorPrintT where lift :: m a -> RecolorPrintT m a lift = m a -> RecolorPrintT m a forall (m :: * -> *) a. m a -> RecolorPrintT m a RecolorPrintT instance MonadTransControl RecolorPrintT where type StT RecolorPrintT a = a liftWith :: (Run RecolorPrintT -> m a) -> RecolorPrintT m a liftWith Run RecolorPrintT -> m a inner = m a -> RecolorPrintT m a forall (m :: * -> *) a. m a -> RecolorPrintT m a RecolorPrintT (m a -> RecolorPrintT m a) -> m a -> RecolorPrintT m a forall a b. (a -> b) -> a -> b $ Run RecolorPrintT -> m a inner Run RecolorPrintT forall (m :: * -> *) a. RecolorPrintT m a -> m a unRecolorPrintT restoreT :: m (StT RecolorPrintT a) -> RecolorPrintT m a restoreT = m (StT RecolorPrintT a) -> RecolorPrintT m a forall (m :: * -> *) a. m a -> RecolorPrintT m a RecolorPrintT instance MonadBaseControl IO m => MonadRecolor (RecolorPrintT m) where recolor :: Trichromaticity -> RecolorPrintT m () recolor = IO () -> RecolorPrintT m () forall (b :: * -> *) (m :: * -> *) α. MonadBase b m => b α -> m α liftBase (IO () -> RecolorPrintT m ()) -> (Trichromaticity -> IO ()) -> Trichromaticity -> RecolorPrintT m () forall b c a. (b -> c) -> (a -> b) -> a -> c . Trichromaticity -> IO () forall a. Show a => a -> IO () print runRecolorPrintT :: RecolorPrintT m a -> m a runRecolorPrintT :: RecolorPrintT m a -> m a runRecolorPrintT = RecolorPrintT m a -> m a forall (m :: * -> *) a. RecolorPrintT m a -> m a unRecolorPrintT