
Hello guys, After some playing around trying to compose enumerators, I went through a different approach and tried instead to compose through Iteratees. The following code does compile correctly 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)) -- ] main :: IO () main = run (enum $$ it) >>= print where enum = enumList 5 [1..] it = foldr (=$) EL.consume [ EL.isolate 100 , EL.filter ((==0) . (`mod` 2)) ] It seems the (=$) operator behaves in a better way than the ($=) operator... When I check the signatures of both functions
:t ($=) ($=) :: Monad m => Enumerator ao m (Step ai m b) -> Enumeratee ao ai m b -> Enumerator ai m b
The original enumerator of type (Enumerator a m b) gets transformed to (Enumerator ao m (Step ai m b)), how this works is beyond me. When checking the type of (=$)
:t ($=) (=$) :: Monad m => Enumeratee ao ai m b -> Iteratee ai m b -> Iteratee ao m b
Returns something with more sense, when using an Iteratee as a base of a
foldr of enumeratees, the response for the next one will always be an Iteratee
ao m b, the return type of the Iteratee is not changed with a Step type
suddenly like in ($=).
I solved my problem, however I'm really curious to know what is going on
with the types when using the ($=) operator, I'm going to investigate on my
part and try to come with some clear explanation, however if anyone can
chime in and give us some insights, they are more than welcome.
Cheers.
Roman.-
2011/10/4 Román González
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
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
2011/10/4 Román González
: 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.