[Haskell] Control.Monad.Writer as Python generator

ChrisK chrisk at MIT.EDU
Fri Apr 15 18:07:05 EDT 2005


>> You are correct.  Moand.Cont yield even runs without -O optimizing,
>> just slower
>> ...
>> Anyone have an idea why ghci can't garbage collect it?
>> Is this an actual bug or an innate quirk of the REPL ?
>
> GHCi does not "compile" with optimizations, without -O the strictness 
> analyzer
> isn't run.

The optimizer is irrelevant to whether it runs in constant space, as 
ghc without '-O' runs it just fine.  The optimizer is only useful for 
speed, which is not the issue.

>  The difference is most likely due to strictness analysis.  A well
> placed strictness annotation or two should be able to make it work in 
> GHCi as
> well.

In this code, adding a strictness $! did not work.

> A similar situation occurs with sum: in GHCi for large inputs it
> overflows the stack, but when compiled with -O it works correctly, 
> this is
> because sum is defined with foldl and not foldl' in GHC.

As for adding one strictness annotation, the brute for approach to 
adding '$!' did not work:

yield :: a -> Cont [a] ()
-- original
--yield x = Cont (\c -> x : c () )
-- original in prefix form
--yield x = Cont (\c -> (((:) x) (c ())))    -- memory exhaustion
-- non-trivial
--yield x = Cont (\c -> (((:) x) $! (c ()))) -- stack overflow
-- silly
--yield x = Cont (\c -> (((:) $! x) (c ()))) -- memory exhaustion
-- definitely silly
--yield x = Cont (\c -> (((:) x) (c $! ()))) -- memory exhaustion

So adding two '$!' to the above looks like a non-starter.  The 
asGenerator definition is

asGenerator :: Cont [a] v -> [a]
asGenerator (Cont f) = f (const [])

which has no useful place to insert a '$!'.  So to use continuations in 
GHCI, it may be necessary to build a new version of Cont and its 
internals, or maybe use the callCC interface?  And I had not luck 
adding '$!' to callCC/Cont or callCC/mapCC versions:

-- yield using callCC
yieldCC x = callCC genContCCArg
     where
     genContCCArg = (\oldGenContFunc ->
                     let
                       newCont  = Cont { runCont = newRunCont }
                       newRunCont =  (\contFunc -> (x:(oldRunCont 
contFunc)))
                       oldRunCont = runCont oldCont
                       oldCont = oldGenContFunc ()
                     in newCont
                    )

-- Use the mysterious mapCont function
yieldM x = callCC genContCCArg
     where
     genContCCArg = (\genContFunc -> mapCont (\xs -> x:xs) (genContFunc 
()))

I found no useful explanation of mapCont via Google.  It was another 
case of deriving the function's action from the type.

Since this is now a "gchi problem", should this be taken to the ghc 
mailing list as well? instead?

-- 
Chris



More information about the Haskell mailing list