Search code examples
haskellhaskell-pipes

Simple program using Pipes hangs


I have the following program, which produces no output when run with runhaskell Toy.hs, and instead hangs indefinitely. By my understanding, the program should print "hi" and then exit. I would appreciate an answer and/or advice about how to debug such an issue. I'm using Pipes 4.0.0 off of github (github.com/Gabriel439/Haskell-Pipes-Library).

module Toy where

import Pipes
import Control.Monad.State

type Request = String
type Response = String

serveChoice :: Request -> Server Request Response IO ()
serveChoice = forever go
  where go req = do
        lift $ putStrLn req
        respond req

run :: Monad m => () -> Client Request Response (StateT Int m) ()
run () = do
    request "hi"
    return ()

main :: IO ()
main = evalStateT (runEffect $ hoist lift . serveChoice >-> run $ ()) 0

Solution

  • You need to use foreverK instead of forever, like this:

    module Toy where
    
    import Pipes
    import Pipes.Prelude (foreverK)
    import Control.Monad.State
    
    type Request = String
    type Response = String
    
    serveChoice :: Request -> Server Request Response IO ()
    serveChoice = foreverK go
      where go req = do
            lift $ putStrLn req
            respond req
    
    run :: Monad m => () -> Client Request Response (StateT Int m) ()
    run () = do
        request "hi"
        return ()
    
    main :: IO ()
    main = evalStateT (runEffect $ hoist lift . serveChoice >-> run $ ()) 0
    

    The reason your original version hangs is that you used forever in the Reader monad (i.e. the ((->) a) monad) and not the pipe monad. Within this monad, forever is equivalent to :

    -- i.e.        m b  ->     m c
    forever :: (a -> b) -> (a -> c)
    forever m = m >> forever m
              = m >>= \_ -> forever m
              = \a -> (\_ -> forever m) (m a) a
              = \a -> forever m a
              = forever m
    

    foreverK is probably what you wanted, since it is the same idiom for Servers introduced in the pipes-3.3.0 tutorial.

    This change fixes the program which now completes normally:

    >>> main
    hi
    >>>