Well, It looks like with 'transformer' look onto iteratees it is
possible to fold two streams without anything except Iteratee, yet some
complications arise. Even real zipping. for example merging two sorted
streams with output stream sorted, is expressible. More preciesely, I
tried to write a separate module (attached) and with careful use of
'runners' I got stack of Iteratee/Enumeratee transformers, that shall do
the job. However, typing of the running function and input streams is a
mess:

t \i e g -> mkEnumeration $ enumerateTo g $ mkIteration $ enumerateTo e
(mkIteration i)
\i e g -> mkEnumeration $ enumerateTo g $ mkIteration $ enumerateTo e
(mkIteration i)
  :: Iteratee e2 a s2 (Iteratee e1 a s1 (Enumeratee e r s m)) a
     -> Enumeration e2 a s2 (Iteratee e1 a s1 (Enumeratee e r s m))
     -> Enumeration e1 a s1 (Enumeratee e r s m)
     -> Enumeration e r s m

And lifting of innermost iteratee's 'nextIM' is not sufficient for merge
of sorting streams: A separate one must be written.
-- | Pure haskell 98 code : datatypes, instances and so on.
-- No fundeps/typefamilies: they will go to separate packages
module Data.Iteration.Types where
import Control.Monad.Trans.Class
import Control.Monad.IO.Class

newtype Enumeration e r s m
 = Enumeration 
 	{ runEnumeration:: m r -- executed if no more input
			-> (e -> m r)  -- executed if error encountered
			-> (s -> Enumeration e r s m -> m r) -- executed if there is more input
			-> m r
	}

newtype Enumeratee e r s m a
 = Enumeratee 
 	{ runEnumeratee	:: ( a -> Enumeration e r s m ) -- how to generate tail of enumeration ?
			-> Enumeration e r s m
	}

instance Monad (Enumeratee e r s m) where
 return a = Enumeratee ( $ a)
 m >>= k  = Enumeratee $ \c -> runEnumeratee m $ \p -> runEnumeratee (k p) c

instance Functor (Enumeratee e r m s) where
 fmap f m = m >>= return . f


instance MonadTrans (Enumeratee e r s) where
 lift m = Enumeratee $ 	\c -> 
	Enumeration $ \pr eh ip -> do
		v <- m 
		runEnumeration (c v) pr eh ip

instance MonadIO m => MonadIO (Enumeratee e r s m) where
 liftIO = lift . liftIO

yield :: s -> Enumeratee e r s m ()
yield s = Enumeratee $ \c -> Enumeration $ \ _ _ n -> n s $ c ()

failE :: e -> Enumeratee e r s m a
failE e = Enumeratee $ \_ -> Enumeration $ \_ eh _ -> eh e

stopE :: Enumeratee e r s m a
stopE = Enumeratee $ \_ -> Enumeration $ \r _ _ -> r 

mkEnumeration :: Enumeratee e r s m a -> Enumeration e r s m
mkEnumeration e = runEnumeratee e $ const $ Enumeration $ \pr _ _ -> pr

enumerateTo :: Enumeration e r s m -> Iteration e r s m -> m r
enumerateTo = flip runIteration

------------------------------------------------------------------

newtype Iteration e r s m
 = Iteration
 	{ runIteration	:: Enumeration e r s m -> m r } 

newtype Iteratee e r s m a 
 = Iteratee 
 	{ runIteratee 	:: ( a -> Iteration e r s m )
 			-> Iteration e r s m
	}

instance Monad (Iteratee e r s m) where
 return a = Iteratee ($ a)
 m >>=  k = Iteratee $ \c -> runIteratee m $ \ a -> runIteratee (k a) c

instance Functor (Iteratee e r s m) where
 fmap f m = m >>= return . f

instance MonadTrans (Iteratee e r s) where
 lift m = Iteratee $ \c ->
 	Iteration $ \e -> do
		v <- m
		runIteration (c v) e

instance MonadIO m => MonadIO (Iteratee e r s m) where
 liftIO = lift . liftIO

stopI :: Monad m => r -> Iteratee e r s m a
stopI r = Iteratee $ \_ -> Iteration $ \_ -> return r

stopIM :: m r -> Iteratee e r s m a
stopIM r = Iteratee $ \_ -> Iteration $ \_ -> r

nextI :: Monad m => r -> (e -> r) -> Iteratee e r s m s
nextI pr eh = Iteratee $ \c -> Iteration $ \e -> 
 runEnumeration e (return pr) (return . eh) $ \s e' -> runIteration (c s) e'

nextIM :: m r -> (e -> m r) -> Iteratee e r s m s 
nextIM pr eh = Iteratee $ \c -> Iteration $ \e -> 
 runEnumeration e pr eh $ \s e' -> runIteration (c s) e'


mkIteration :: Monad m => Iteratee e a s m a -> Iteration e a s m
mkIteration i = runIteratee i $ \v -> Iteration $ \_ -> return v


------------------------------------------------------------------




_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to