Re: [Haskell-cafe] A home-brew iteration-alike library: some extension quiestions

2010-12-13 Thread Permjacov Evgeniy
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


Re: [Haskell-cafe] A home-brew iteration-alike library: some extension quiestions

2010-12-13 Thread John Lato
From: Permjacov Evgeniy permea...@gmail.com


 Hi. I Wrote a simple iteration library. It was not intensively tested,
 so it MAY contatin bugs, but it is very unlikely. The library is
 currently on github: https://github.com/permeakra/iteration

 I'm not ready to upload it to hackage, as some testing and extension is
 really needed. However, I'd like to know about possible flaws.

 Current goal is addition of byte-stream (de)compression and IO functions
 extenstion. After this package will be cabalized and uploaded to
 hackage. So, while design is not frozen yet, I'm interested in criticism
 -)/


First, I haven't examined your code in sufficient depth to fully understand
it, so I may be off the mark with this comment.  However, I'm not convinced
it's possible to safely implement zipping in iteration-style IO without
another technique (e.g. monadic regions), by which I mean I suspect any code
which exposes enough control to pause an enumeration (or alternatively
allows a user-supplied termination check to the enumerator) will also not
provide guaranteed finalization/garbage collection of the underlying
resource (e.g. handle).

I also require zipping of streams, and in fact it is possible with
iteratee.  I haven't included the code in the library because I was formerly
not convinced of its safety.  I do think it's safe now, but only by use of a
monadic region.

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


Re: [Haskell-cafe] A home-brew iteration-alike library: some extension quiestions

2010-12-13 Thread John Lato
From: o...@okmij.org


 Just for the record: the library IterateeM.hs, uses NO extensions to
 Haskell98, let alone Haskell2010. The library as written requires
 LowLevelIO.hs, which uses FFI (which has been Haskell98 addendum and
 is in proper Haskell2010). The sample code, Wc.hs, for example, is
 Haskell98. So, the iteratee can be written with no extensions
 whatsoever.


Related to this, IterateeM.hs and LowLevelIO.hs don't use runtime exceptions
either, which I consider a particularly nice feature.



 In particular, IterateeM does not use any monad transformer library
 (although it could have). I found that the trouble of writing a state
 monad for a particular state is negligible compared to the pain of
 choosing a particular monad transformer library, and especially the
 pain inflicted on the users who have to deal with many a conflicts of
 monad transformer libraries.


  The problem was that I wished Zippee. It means that external enumerator
  must be suspended at some points so Zippee can process elements from
  both left and right streams in desired order. It makes any other
  approach I considered impossible to use.

 The file IterateeN.hs demonstrates zipping two streams together (in
 lock-step and not in-lockstep). It turns out, the existing Iteratee
 interface and type suffices. This is described in more detail in:

 Parallel composition of iteratees: one source to several sinks
 http://okmij.org/ftp/Streams.html#1enum2iter

 Parallel composition of streams: several sources to one sink
 http://okmij.org/ftp/Streams.html#2enum1iter


It seems I was mistaken in my last reply.  That's what I get for answering
before I read through all my weekend email.

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


Re: [Haskell-cafe] A home-brew iteration-alike library: some extension quiestions

2010-12-12 Thread oleg

Just for the record: the library IterateeM.hs, uses NO extensions to
Haskell98, let alone Haskell2010. The library as written requires
LowLevelIO.hs, which uses FFI (which has been Haskell98 addendum and
is in proper Haskell2010). The sample code, Wc.hs, for example, is
Haskell98. So, the iteratee can be written with no extensions
whatsoever.

In particular, IterateeM does not use any monad transformer library
(although it could have). I found that the trouble of writing a state
monad for a particular state is negligible compared to the pain of
choosing a particular monad transformer library, and especially the
pain inflicted on the users who have to deal with many a conflicts of
monad transformer libraries.


 The problem was that I wished Zippee. It means that external enumerator
 must be suspended at some points so Zippee can process elements from
 both left and right streams in desired order. It makes any other
 approach I considered impossible to use.

The file IterateeN.hs demonstrates zipping two streams together (in
lock-step and not in-lockstep). It turns out, the existing Iteratee
interface and type suffices. This is described in more detail in:

Parallel composition of iteratees: one source to several sinks
http://okmij.org/ftp/Streams.html#1enum2iter

Parallel composition of streams: several sources to one sink
http://okmij.org/ftp/Streams.html#2enum1iter


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


Re: [Haskell-cafe] A home-brew iteration-alike library: some extension quiestions

2010-12-11 Thread Henning Thielemann
John Millikin schrieb:
 On Thu, Dec 9, 2010 at 12:43, Michael Snoyman mich...@snoyman.com wrote:
 For the record, enumerator (and I believe iteratee as well) uses
 transformers, not mtl. transformers itself is Haskell98; all FunDep
 code is separated out to monads-fd.

 Michael
 
 iteratee also uses 'transformers', but requires several extensions;
 see  
 http://hackage.haskell.org/packages/archive/iteratee/0.6.0.1/doc/html/src/Data-Iteratee-Base.html
 
 It seems silly to avoid extensions, though; every non-trivial package
 on Hackage depends on them, either directly or via a dependency. For
 example, though 'enumerator' requires no extensions itself, it depends
 on both 'text' and 'bytestring', which require a ton of them.

It's not silly. If you want to use other compilers like JHC, you are
lucky if the used packages are simply Haskell 98. Haskell 98 is already
complicated enough. I am often very annoyed if a package imports only a
simple utility function from another package that in turn depends on
multiple packages that in the end require all available GHC extensions.
Also using a GHC extension is often the consequence of a design flaw.
E.g. (instance C String where) is possible, but the Haskell 98 solutions
to it are usually cleaner. My slogan is: Solve simple problems the
simple way. Most of my packages are Haskell 98.

http://www.haskell.org/haskellwiki/Use_of_language_extensions

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


Re: [Haskell-cafe] A home-brew iteration-alike library: some extension quiestions

2010-12-11 Thread Henning Thielemann
Antoine Latter schrieb:

 It's a mater of taste which way to go, but I prefer importing modules
 qualified rather than have type-suffixes on functions - so I would
 rather use 'I.next' and 'A.next' instead of 'nextI' and 'nextA'. But
 reasonable people can disagree on this.

http://www.haskell.org/haskellwiki/Qualified_names

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


Re: [Haskell-cafe] A home-brew iteration-alike library: some extension quiestions

2010-12-09 Thread Antoine Latter
I only have some surface level questions/comments -

What existing packages is this similar to? How is it different from
any previous work in the area?

Also, likes looks like you don't need the 'Monad m' constraint on your
various Monad and Functor instances in Data.Iteration.Types, which I
think is one of the nicest properties of the continuation-based
approach to something like this.

It's a mater of taste which way to go, but I prefer importing modules
qualified rather than have type-suffixes on functions - so I would
rather use 'I.next' and 'A.next' instead of 'nextI' and 'nextA'. But
reasonable people can disagree on this.

Take care,
Antoine

On Thu, Dec 9, 2010 at 1:42 PM, Permjacov Evgeniy permea...@gmail.com wrote:
 Hi. I Wrote a simple iteration library. It was not intensively tested,
 so it MAY contatin bugs, but it is very unlikely. The library is
 currently on github: https://github.com/permeakra/iteration

 I'm not ready to upload it to hackage, as some testing and extension is
 really needed. However, I'd like to know about possible flaws.

 Current goal is addition of byte-stream (de)compression and IO functions
 extenstion. After this package will be cabalized and uploaded to
 hackage. So, while design is not frozen yet, I'm interested in criticism -)/


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


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


Re: [Haskell-cafe] A home-brew iteration-alike library: some extension quiestions

2010-12-09 Thread Permjacov Evgeniy


 Original Message 
Subject:Re: [Haskell-cafe] A home-brew iteration-alike library: some
extension quiestions
Date:   Thu, 09 Dec 2010 23:07:49 +0300
From:   Permjacov Evgeniy permea...@gmail.com
To: Antoine Latter aslat...@gmail.com



On 12/09/2010 10:54 PM, Antoine Latter wrote:
 I only have some surface level questions/comments -

 What existing packages is this similar to? How is it different from
 any previous work in the area?

Main idea was taken from Iteratees invented by Oleg Kiselev (there are
two packages on hackage implementing this ideas: data-iteraties and
enumerator packages)
The difference is, that I wished haskell-2010 compilant package for
left-foldable streams, including support for easy builing, transcoding,
merging and folding of streams relying on do-notation (see
Data.Iteration.Unicode.* for examples of transcoding streams: it is
quite clean and easily understandable) and ability to specify easily
monadic actions in stream processors.
 Also, likes looks like you don't need the 'Monad m' constraint on your
 various Monad and Functor instances in Data.Iteration.Types, which I
 think is one of the nicest properties of the continuation-based
 approach to something like this.
Errgh. That may be true, but I did not consider non-monadic context at
all, so I enforced this constrain mindlessly
 It's a mater of taste which way to go, but I prefer importing modules
 qualified rather than have type-suffixes on functions - so I would
 rather use 'I.next' and 'A.next' instead of 'nextI' and 'nextA'. But
 reasonable people can disagree on this.

 Take care,
 Antoine
Thanks!
 On Thu, Dec 9, 2010 at 1:42 PM, Permjacov Evgeniy permea...@gmail.com wrote:
 Hi. I Wrote a simple iteration library. It was not intensively tested,
 so it MAY contatin bugs, but it is very unlikely. The library is
 currently on github: https://github.com/permeakra/iteration

 I'm not ready to upload it to hackage, as some testing and extension is
 really needed. However, I'd like to know about possible flaws.

 Current goal is addition of byte-stream (de)compression and IO functions
 extenstion. After this package will be cabalized and uploaded to
 hackage. So, while design is not frozen yet, I'm interested in criticism -)/


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


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


Re: [Haskell-cafe] A home-brew iteration-alike library: some extension quiestions

2010-12-09 Thread Antoine Latter
Also, one thing that tripped me up is that your Stream type is
fundamentally different from the Stream types in the
iteratee/enumerator libraries - yours is more of a monadic list in the
inner monad, with explicit errors.

How does this change the operation of the Iterator type?

I hope I am not pestering you too much :-)

I think it is really fascinating how many different approaches people
have to the left-fold-enumerator idea, and it is hard for me to grasp
which differences are fundamental and what the differences mean.

Also, in what way are the other libraries not Haskell-2010 compliant?
I haven't experimented too much with this sort of thing, since Cabal
defaults to the Haskell '98 language, and that's how I install most
things.

Thanks for your response,
Antoine

On Thu, Dec 9, 2010 at 2:07 PM, Permjacov Evgeniy permea...@gmail.com wrote:
 On 12/09/2010 10:54 PM, Antoine Latter wrote:
 I only have some surface level questions/comments -

 What existing packages is this similar to? How is it different from
 any previous work in the area?

 Main idea was taken from Iteratees invented by Oleg Kiselev (there are
 two packages on hackage implementing this ideas: data-iteraties and
 enumerator packages)
 The difference is, that I wished haskell-2010 compilant package for
 left-foldable streams, including support for easy builing, transcoding,
 merging and folding of streams relying on do-notation (see
 Data.Iteration.Unicode.* for examples of transcoding streams: it is
 quite clean and easily understandable) and ability to specify easily
 monadic actions in stream processors.
 Also, likes looks like you don't need the 'Monad m' constraint on your
 various Monad and Functor instances in Data.Iteration.Types, which I
 think is one of the nicest properties of the continuation-based
 approach to something like this.
 Errgh. That may be true, but I did not consider non-monadic context at
 all, so I enforced this constrain mindlessly
 It's a mater of taste which way to go, but I prefer importing modules
 qualified rather than have type-suffixes on functions - so I would
 rather use 'I.next' and 'A.next' instead of 'nextI' and 'nextA'. But
 reasonable people can disagree on this.

 Take care,
 Antoine
 Thanks!
 On Thu, Dec 9, 2010 at 1:42 PM, Permjacov Evgeniy permea...@gmail.com 
 wrote:
 Hi. I Wrote a simple iteration library. It was not intensively tested,
 so it MAY contatin bugs, but it is very unlikely. The library is
 currently on github: https://github.com/permeakra/iteration

 I'm not ready to upload it to hackage, as some testing and extension is
 really needed. However, I'd like to know about possible flaws.

 Current goal is addition of byte-stream (de)compression and IO functions
 extenstion. After this package will be cabalized and uploaded to
 hackage. So, while design is not frozen yet, I'm interested in criticism -)/


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




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


Re: [Haskell-cafe] A home-brew iteration-alike library: some extension quiestions

2010-12-09 Thread Permjacov Evgeniy
On 12/09/2010 11:17 PM, Antoine Latter wrote:
 Also, one thing that tripped me up is that your Stream type is
 fundamentally different from the Stream types in the
 iteratee/enumerator libraries - yours is more of a monadic list in the
 inner monad, with explicit errors.

 How does this change the operation of the Iterator type?
The problem was that I wished Zippee. It means that external enumerator
must be suspended at some points so Zippee can process elements from
both left and right streams in desired order. It makes any other
approach I considered impossible to use.

 Also, in what way are the other libraries not Haskell-2010 compliant?
 I haven't experimented too much with this sort of thing, since Cabal
 defaults to the Haskell '98 language, and that's how I install most 
 things.
Haskell-2010 does not include functional dependencies (wich are
considered evil by many) and, as I recall, type families. This makes mtl
haskell-2010 and haskell-98 uncompilant -(. Functional dependencies and
type familes are tricky things, so it is better to avoid them.
 Thanks for your response,
 Antoine

 On Thu, Dec 9, 2010 at 2:07 PM, Permjacov Evgeniy permea...@gmail.com wrote:
 On 12/09/2010 10:54 PM, Antoine Latter wrote:
 I only have some surface level questions/comments -

 What existing packages is this similar to? How is it different from
 any previous work in the area?

 Main idea was taken from Iteratees invented by Oleg Kiselev (there are
 two packages on hackage implementing this ideas: data-iteraties and
 enumerator packages)
 The difference is, that I wished haskell-2010 compilant package for
 left-foldable streams, including support for easy builing, transcoding,
 merging and folding of streams relying on do-notation (see
 Data.Iteration.Unicode.* for examples of transcoding streams: it is
 quite clean and easily understandable) and ability to specify easily
 monadic actions in stream processors.
 Also, likes looks like you don't need the 'Monad m' constraint on your
 various Monad and Functor instances in Data.Iteration.Types, which I
 think is one of the nicest properties of the continuation-based
 approach to something like this.
 Errgh. That may be true, but I did not consider non-monadic context at
 all, so I enforced this constrain mindlessly
 It's a mater of taste which way to go, but I prefer importing modules
 qualified rather than have type-suffixes on functions - so I would
 rather use 'I.next' and 'A.next' instead of 'nextI' and 'nextA'. But
 reasonable people can disagree on this.

 Take care,
 Antoine
 Thanks!
 On Thu, Dec 9, 2010 at 1:42 PM, Permjacov Evgeniy permea...@gmail.com 
 wrote:
 Hi. I Wrote a simple iteration library. It was not intensively tested,
 so it MAY contatin bugs, but it is very unlikely. The library is
 currently on github: https://github.com/permeakra/iteration

 I'm not ready to upload it to hackage, as some testing and extension is
 really needed. However, I'd like to know about possible flaws.

 Current goal is addition of byte-stream (de)compression and IO functions
 extenstion. After this package will be cabalized and uploaded to
 hackage. So, while design is not frozen yet, I'm interested in criticism 
 -)/


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




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


Re: [Haskell-cafe] A home-brew iteration-alike library: some extension quiestions

2010-12-09 Thread Michael Snoyman
On Thu, Dec 9, 2010 at 10:32 PM, Permjacov Evgeniy permea...@gmail.com wrote:
 On 12/09/2010 11:17 PM, Antoine Latter wrote:
 Also, one thing that tripped me up is that your Stream type is
 fundamentally different from the Stream types in the
 iteratee/enumerator libraries - yours is more of a monadic list in the
 inner monad, with explicit errors.

 How does this change the operation of the Iterator type?
 The problem was that I wished Zippee. It means that external enumerator
 must be suspended at some points so Zippee can process elements from
 both left and right streams in desired order. It makes any other
 approach I considered impossible to use.

 Also, in what way are the other libraries not Haskell-2010 compliant?
 I haven't experimented too much with this sort of thing, since Cabal
 defaults to the Haskell '98 language, and that's how I install most
 things.
 Haskell-2010 does not include functional dependencies (wich are
 considered evil by many) and, as I recall, type families. This makes mtl
 haskell-2010 and haskell-98 uncompilant -(. Functional dependencies and
 type familes are tricky things, so it is better to avoid them.

For the record, enumerator (and I believe iteratee as well) uses
transformers, not mtl. transformers itself is Haskell98; all FunDep
code is separated out to monads-fd.

Michael

 Thanks for your response,
 Antoine

 On Thu, Dec 9, 2010 at 2:07 PM, Permjacov Evgeniy permea...@gmail.com 
 wrote:
 On 12/09/2010 10:54 PM, Antoine Latter wrote:
 I only have some surface level questions/comments -

 What existing packages is this similar to? How is it different from
 any previous work in the area?

 Main idea was taken from Iteratees invented by Oleg Kiselev (there are
 two packages on hackage implementing this ideas: data-iteraties and
 enumerator packages)
 The difference is, that I wished haskell-2010 compilant package for
 left-foldable streams, including support for easy builing, transcoding,
 merging and folding of streams relying on do-notation (see
 Data.Iteration.Unicode.* for examples of transcoding streams: it is
 quite clean and easily understandable) and ability to specify easily
 monadic actions in stream processors.
 Also, likes looks like you don't need the 'Monad m' constraint on your
 various Monad and Functor instances in Data.Iteration.Types, which I
 think is one of the nicest properties of the continuation-based
 approach to something like this.
 Errgh. That may be true, but I did not consider non-monadic context at
 all, so I enforced this constrain mindlessly
 It's a mater of taste which way to go, but I prefer importing modules
 qualified rather than have type-suffixes on functions - so I would
 rather use 'I.next' and 'A.next' instead of 'nextI' and 'nextA'. But
 reasonable people can disagree on this.

 Take care,
 Antoine
 Thanks!
 On Thu, Dec 9, 2010 at 1:42 PM, Permjacov Evgeniy permea...@gmail.com 
 wrote:
 Hi. I Wrote a simple iteration library. It was not intensively tested,
 so it MAY contatin bugs, but it is very unlikely. The library is
 currently on github: https://github.com/permeakra/iteration

 I'm not ready to upload it to hackage, as some testing and extension is
 really needed. However, I'd like to know about possible flaws.

 Current goal is addition of byte-stream (de)compression and IO functions
 extenstion. After this package will be cabalized and uploaded to
 hackage. So, while design is not frozen yet, I'm interested in criticism 
 -)/


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




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


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


Re: [Haskell-cafe] A home-brew iteration-alike library: some extension quiestions

2010-12-09 Thread John Millikin
On Thu, Dec 9, 2010 at 12:43, Michael Snoyman mich...@snoyman.com wrote:
 For the record, enumerator (and I believe iteratee as well) uses
 transformers, not mtl. transformers itself is Haskell98; all FunDep
 code is separated out to monads-fd.

 Michael

iteratee also uses 'transformers', but requires several extensions;
see  
http://hackage.haskell.org/packages/archive/iteratee/0.6.0.1/doc/html/src/Data-Iteratee-Base.html


It seems silly to avoid extensions, though; every non-trivial package
on Hackage depends on them, either directly or via a dependency. For
example, though 'enumerator' requires no extensions itself, it depends
on both 'text' and 'bytestring', which require a ton of them.

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