[Haskell-cafe] Composing a list of Enumeratees into an Enumerator using ($=)

Román González romanandreg at gmail.com
Tue Oct 4 09:42:59 CEST 2011


Hello Conrad,


Thanks for taking the time to answer back. Actually I don't want to do
anything fancy, I just want to compose a list of Enumeratees together into
an Enumerator, using the same type for both ao and ai, I suspect it doesn't
matter what the type of this ao and ai are, I would obtain the same error
using this simpler example:

module Main where

import Data.List (foldl')
import Data.Enumerator hiding (foldl')
import qualified Data.Enumerator.List as EL

-- This is what I orginally have
main :: IO ()
main = run_ (((enumList 5 [1..] $=
               EL.isolate 100) $=
               EL.filter ((== 0) . (`mod` 2))) $$
               EL.consume) >>=
       print

-- This is what I want and for some reason is not
-- compiling (infinite type error)
--main2 :: IO ()
--main2 = run (enum $$ EL.consume) >>= print
-- where
--   enum = foldl' ($=)
--                 (enumList 5 [1..])
--                 [ EL.isolate 100
--                 , EL.filter ((==0) . (`mod` 2))
--                 ]



For some complicated type logic, main2 won't compile, I'm trying to figure
out a way to actually do this. The reason why I want to do the composition
through list is because I'm mapping input parameters (from
System.Environment.getArgs) to a list of Enumeratees, and I want to compose
them dynamically.

Hope this helps.

Roman.-

2011/10/3 Conrad Parker <conrad at metadecks.org>

> 2011/10/4 Román González <romanandreg at gmail.com>:
> > Hey guys,
> >
> > Right now I'm facing with a type problem that is really nasty, I want to
> > compose a list of enumeratees using the ($=) operator to create a new
> > enumerator.  Whenever I'm trying to use the foldx function in conjunction
> > with ($=) I get this error:
> >
> >> :t foldr ($=)
> >
> > <interactive>:1:7:
> >     Occurs check: cannot construct the infinite type:
> >       b0 = Step ao0 m0 b0
> >     Expected type: Enumerator ao0 m0 (Step ao0 m0 b0)
> >                    -> Enumeratee ao0 ao0 m0 b0
> >                    -> Enumeratee ao0 ao0 m0 b0
> >       Actual type: Enumerator ao0 m0 (Step ao0 m0 b0)
> >                    -> Enumeratee ao0 ao0 m0 b0
> >                    -> Enumerator ao0 m0 b0
> >     In the first argument of `foldr', namely `($=)'
> >     In the expression: foldr ($=)
> >
> >> :t Prelude.foldl ($=)
> >
> > <interactive>:1:15:
> >     Occurs check: cannot construct the infinite type:
> >       b0 = Step ao0 m0 b0
> >     Expected type: Enumerator ao0 m0 (Step ao0 m0 b0)
> >                    -> Enumeratee ao0 ao0 m0 b0
> >                    -> Enumerator ao0 m0 (Step ao0 m0 b0)
> >       Actual type: Enumerator ao0 m0 (Step ao0 m0 b0)
> >                    -> Enumeratee ao0 ao0 m0 b0
> >                    -> Enumerator ao0 m0 b0
> >     In the first argument of `Prelude.foldl', namely `($=)'
> >     In the expression: Prelude.foldl ($=)
> >
> > <interactive>:1:15:
> >     Occurs check: cannot construct the infinite type:
> >       b0 = Step ao0 m0 b0
> >     Expected type: Enumerator ao0 m0 (Step ao0 m0 b0)
> >                    -> Enumeratee ao0 ao0 m0 b0
> >                    -> Enumerator ao0 m0 (Step ao0 m0 b0)
> >       Actual type: Enumerator ao0 m0 (Step ao0 m0 b0)
> >                    -> Enumeratee ao0 ao0 m0 b0
> >                    -> Enumerator ao0 m0 b0
> >     In the first argument of `Prelude.foldl', namely `($=)'
> >     In the expression: Prelude.foldl ($=)
> >
> > Obviously there is something I don't quite understand about the ($=) (=$)
> > functions, how can one compose a list of enumeratees, is it even
> possible?
>
> Hi,
>
> what are you trying to actually do, ie. what kind of data are you
> trying to transform, what are the inputs and outputs of each
> enumeratee?
>
> are you trying to feed the output of the first enumeratee into the
> input of the second, and so on? or are you trying to run them all in
> parallel?
>
> Conrad.
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20111004/3e521110/attachment-0001.htm>


More information about the Haskell-Cafe mailing list