module Text.Parser.Internal where import Control.Applicative (Applicative, liftA2) import qualified Control.Monad.Trans.Writer.Lazy as Lazy (WriterT(WriterT)) import qualified Control.Monad.Trans.Writer.Strict as Strict (WriterT(WriterT)) import qualified Control.Monad.Trans.State.Lazy as Lazy (StateT(StateT)) import qualified Control.Monad.Trans.State.Strict as Strict (StateT(StateT)) import qualified Control.Monad.Trans.RWS.Lazy as Lazy (RWST(RWST)) import qualified Control.Monad.Trans.RWS.Strict as Strict (RWST(RWST)) mapLazyWriterT :: Applicative m => (m a -> m b) -> Lazy.WriterT w m a -> Lazy.WriterT w m b mapLazyWriterT :: (m a -> m b) -> WriterT w m a -> WriterT w m b mapLazyWriterT m a -> m b f (Lazy.WriterT m (a, w) p) = m (b, w) -> WriterT w m b forall w (m :: * -> *) a. m (a, w) -> WriterT w m a Lazy.WriterT (m (a, w) -> m (b, w) forall b. m (a, b) -> m (b, b) apply m (a, w) p) where apply :: m (a, b) -> m (b, b) apply m (a, b) m = (b -> b -> (b, b)) -> m b -> m b -> m (b, b) forall (f :: * -> *) a b c. Applicative f => (a -> b -> c) -> f a -> f b -> f c liftA2 (,) (m a -> m b f (m a -> m b) -> m a -> m b forall a b. (a -> b) -> a -> b $ (a, b) -> a forall a b. (a, b) -> a fst ((a, b) -> a) -> m (a, b) -> m a forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> m (a, b) m) ((a, b) -> b forall a b. (a, b) -> b snd ((a, b) -> b) -> m (a, b) -> m b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> m (a, b) m) mapStrictWriterT :: Applicative m => (m a -> m b) -> Strict.WriterT w m a -> Strict.WriterT w m b mapStrictWriterT :: (m a -> m b) -> WriterT w m a -> WriterT w m b mapStrictWriterT m a -> m b f (Strict.WriterT m (a, w) p) = m (b, w) -> WriterT w m b forall w (m :: * -> *) a. m (a, w) -> WriterT w m a Strict.WriterT (m (a, w) -> m (b, w) forall b. m (a, b) -> m (b, b) apply m (a, w) p) where apply :: m (a, b) -> m (b, b) apply m (a, b) m = (b -> b -> (b, b)) -> m b -> m b -> m (b, b) forall (f :: * -> *) a b c. Applicative f => (a -> b -> c) -> f a -> f b -> f c liftA2 (,) (m a -> m b f (m a -> m b) -> m a -> m b forall a b. (a -> b) -> a -> b $ (a, b) -> a forall a b. (a, b) -> a fst ((a, b) -> a) -> m (a, b) -> m a forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> m (a, b) m) ((a, b) -> b forall a b. (a, b) -> b snd ((a, b) -> b) -> m (a, b) -> m b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> m (a, b) m) mapLazyStateT :: Applicative m => (m a -> m b) -> Lazy.StateT w m a -> Lazy.StateT w m b mapLazyStateT :: (m a -> m b) -> StateT w m a -> StateT w m b mapLazyStateT m a -> m b f (Lazy.StateT w -> m (a, w) p) = (w -> m (b, w)) -> StateT w m b forall s (m :: * -> *) a. (s -> m (a, s)) -> StateT s m a Lazy.StateT (m (a, w) -> m (b, w) forall b. m (a, b) -> m (b, b) apply (m (a, w) -> m (b, w)) -> (w -> m (a, w)) -> w -> m (b, w) forall b c a. (b -> c) -> (a -> b) -> a -> c . w -> m (a, w) p) where apply :: m (a, b) -> m (b, b) apply m (a, b) m = (b -> b -> (b, b)) -> m b -> m b -> m (b, b) forall (f :: * -> *) a b c. Applicative f => (a -> b -> c) -> f a -> f b -> f c liftA2 (,) (m a -> m b f (m a -> m b) -> m a -> m b forall a b. (a -> b) -> a -> b $ (a, b) -> a forall a b. (a, b) -> a fst ((a, b) -> a) -> m (a, b) -> m a forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> m (a, b) m) ((a, b) -> b forall a b. (a, b) -> b snd ((a, b) -> b) -> m (a, b) -> m b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> m (a, b) m) mapStrictStateT :: Applicative m => (m a -> m b) -> Strict.StateT s m a -> Strict.StateT s m b mapStrictStateT :: (m a -> m b) -> StateT s m a -> StateT s m b mapStrictStateT m a -> m b f (Strict.StateT s -> m (a, s) p) = (s -> m (b, s)) -> StateT s m b forall s (m :: * -> *) a. (s -> m (a, s)) -> StateT s m a Strict.StateT (m (a, s) -> m (b, s) forall b. m (a, b) -> m (b, b) apply (m (a, s) -> m (b, s)) -> (s -> m (a, s)) -> s -> m (b, s) forall b c a. (b -> c) -> (a -> b) -> a -> c . s -> m (a, s) p) where apply :: m (a, b) -> m (b, b) apply m (a, b) m = (b -> b -> (b, b)) -> m b -> m b -> m (b, b) forall (f :: * -> *) a b c. Applicative f => (a -> b -> c) -> f a -> f b -> f c liftA2 (,) (m a -> m b f (m a -> m b) -> m a -> m b forall a b. (a -> b) -> a -> b $ (a, b) -> a forall a b. (a, b) -> a fst ((a, b) -> a) -> m (a, b) -> m a forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> m (a, b) m) ((a, b) -> b forall a b. (a, b) -> b snd ((a, b) -> b) -> m (a, b) -> m b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> m (a, b) m) mapLazyRWST :: Applicative m => (m a -> m b) -> Lazy.RWST r w s m a -> Lazy.RWST r w s m b mapLazyRWST :: (m a -> m b) -> RWST r w s m a -> RWST r w s m b mapLazyRWST m a -> m b f (Lazy.RWST r -> s -> m (a, s, w) p) = (r -> s -> m (b, s, w)) -> RWST r w s m b forall r w s (m :: * -> *) a. (r -> s -> m (a, s, w)) -> RWST r w s m a Lazy.RWST (\r r-> m (a, s, w) -> m (b, s, w) forall b c. m (a, b, c) -> m (b, b, c) apply (m (a, s, w) -> m (b, s, w)) -> (s -> m (a, s, w)) -> s -> m (b, s, w) forall b c a. (b -> c) -> (a -> b) -> a -> c . r -> s -> m (a, s, w) p r r) where apply :: m (a, b, c) -> m (b, b, c) apply m (a, b, c) m = (b -> (a, b, c) -> (b, b, c)) -> m b -> m (a, b, c) -> m (b, b, c) forall (f :: * -> *) a b c. Applicative f => (a -> b -> c) -> f a -> f b -> f c liftA2 b -> (a, b, c) -> (b, b, c) forall a a b c. a -> (a, b, c) -> (a, b, c) replaceFstOf3 (m a -> m b f (m a -> m b) -> m a -> m b forall a b. (a -> b) -> a -> b $ (a, b, c) -> a forall a b c. (a, b, c) -> a fstOf3 ((a, b, c) -> a) -> m (a, b, c) -> m a forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> m (a, b, c) m) m (a, b, c) m mapStrictRWST :: Applicative m => (m a -> m b) -> Strict.RWST r w s m a -> Strict.RWST r w s m b mapStrictRWST :: (m a -> m b) -> RWST r w s m a -> RWST r w s m b mapStrictRWST m a -> m b f (Strict.RWST r -> s -> m (a, s, w) p) = (r -> s -> m (b, s, w)) -> RWST r w s m b forall r w s (m :: * -> *) a. (r -> s -> m (a, s, w)) -> RWST r w s m a Strict.RWST (\r r-> m (a, s, w) -> m (b, s, w) forall b c. m (a, b, c) -> m (b, b, c) apply (m (a, s, w) -> m (b, s, w)) -> (s -> m (a, s, w)) -> s -> m (b, s, w) forall b c a. (b -> c) -> (a -> b) -> a -> c . r -> s -> m (a, s, w) p r r) where apply :: m (a, b, c) -> m (b, b, c) apply m (a, b, c) m = (b -> (a, b, c) -> (b, b, c)) -> m b -> m (a, b, c) -> m (b, b, c) forall (f :: * -> *) a b c. Applicative f => (a -> b -> c) -> f a -> f b -> f c liftA2 b -> (a, b, c) -> (b, b, c) forall a a b c. a -> (a, b, c) -> (a, b, c) replaceFstOf3 (m a -> m b f (m a -> m b) -> m a -> m b forall a b. (a -> b) -> a -> b $ (a, b, c) -> a forall a b c. (a, b, c) -> a fstOf3 ((a, b, c) -> a) -> m (a, b, c) -> m a forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> m (a, b, c) m) m (a, b, c) m fstOf3 :: (a, b, c) -> a fstOf3 (a a, b b, c c) = a a replaceFstOf3 :: a -> (a, b, c) -> (a, b, c) replaceFstOf3 a a (a _, b b, c c) = (a a, b b, c c)