Search code examples
haskellhaskell-pipeshaskell-pipes-safe

Haskell-pipes: how to use drawAll to test a producer with a MonadSafe constraint?


I have a producer which, given a path, traverses the filesystem yielding Haskell files' paths. It's built on top of pipes-files:

import Pipes
import Pipes.Files
import Pipes.Safe
import qualified Pipes.Prelude as P
import Data.Monoid ((<>))
import Data.List (isSuffixOf)
import System.Directory (doesFileExist)


-- | Starting from a path, generate a sequence of paths corresponding
--   to Haskell files. The fileystem is traversed depth-first.
allFiles :: (MonadIO m, MonadSafe m) => FilePath -> IO (Producer FilePath m ())
allFiles path = do
    isFile <- doesFileExist path
    if isFile then return $ each [path] >-> P.filter (".hs" `isSuffixOf`)
              else return $ find path (glob "*.hs" <> regular)

Now I'd like to test it with Hspec, but I'm finding it hard to transform the producer into a list. It would be simpler, were it not for that MonadSafe m constraint which causes a lot of type errors. Here is what I wrote:

import Pipes
import Pipes.Safe
import Pipes.Parse
import Test.Hspec


shouldReturnP :: (MonadIO m, MonadSafe m)
              => IO (Producer FilePath m ()) -> [FilePath] -> Expectation
shouldReturnP action res = do
    prod <- action
    let paths = runSafeT $ evalStateT drawAll prod
    paths `shouldBe` res

This is how it should be used:

spec :: Spec
spec = do
    describe "allFiles" $
        it "traverses the filesystem depth-first returning only hs files" $
            allFiles ("test" </> "tree") `shouldReturnP`
                [ "test" </> "tree" </> "a.hs"
                , "test" </> "tree" </> "sub"  </> "b.hs"
                , "test" </> "tree" </> "sub"  </> "c.hs"
                , "test" </> "tree" </> "sub2" </> "a.hs"
                , "test" </> "tree" </> "sub2" </> "e.hs"
                ]

Compiling the tests gives the following errors:

test/Spec.hs:57:47:
    Couldn't match type ‘m’ with ‘Pipes.Safe.SafeT []’
      ‘m’ is a rigid type variable bound by
          the type signature for
            shouldReturnP :: (MonadIO m, MonadSafe m) =>
                             IO (Producer FilePath m ()) -> [FilePath] -> Expectation
          at test/Spec.hs:53:18
    Expected type: Producer FilePath (Pipes.Safe.SafeT []) ()
      Actual type: Producer FilePath m ()
    Relevant bindings include
      prod :: Producer FilePath m () (bound at test/Spec.hs:56:5)
      action :: IO (Producer FilePath m ())
        (bound at test/Spec.hs:55:15)
      shouldReturnP :: IO (Producer FilePath m ())
                       -> [FilePath] -> Expectation
        (bound at test/Spec.hs:55:1)
    In the second argument of ‘evalStateT’, namely ‘prod’
    In the second argument of ‘($)’, namely ‘evalStateT drawAll prod’

test/Spec.hs:58:22:
    Couldn't match type ‘Char’ with ‘[Char]’
    Expected type: [[FilePath]]
      Actual type: [FilePath]
    In the second argument of ‘shouldBe’, namely ‘res’
    In a stmt of a 'do' block: paths  res

Solution

  • How about using toListM from Pipes.Prelude:

    ...
    import qualified Pipes.Prelude as P
    ...
    
    files1 :: (MonadIO m, MonadSafe m) => Producer FilePath m ()
    files1 = find "." (glob "*.hs" <> regular)
    
    test1 = do
      got <- runSafeT $ runEffect $ P.toListM files1
      shouldBe got ["a.hs", "b.hs", "c.hs"]
    
    -- using `allFiles`:
    
    test2 = do
      prod <- allFiles "."
      got <- runSafeT $ runEffect $ P.toListM prod
      shouldBe got ["a.hs", "b.hs"]
    

    To write your shouldReturnP function, start with this:

    shouldReturnP1 prod expected = do
      let _ = expected :: [FilePath]
      got <- runSafeT $ P.toListM prod
      shouldBe got expected
    

    and have ghc tell you what the type is, which is:

    shouldReturnP1
      :: (Eq a, Show a) => Producer a (SafeT IO) () -> [a] -> IO ()
    

    You can test it with:

    testP1 = shouldReturnP1 files1 ["a.hs", "b.hs", "c.hs"]
    

    For the IO-action version, write:

    shouldReturnP2 action expected = do
      let _ = expected :: [FilePath]
      prod <- action
      paths <- runSafeT $ runEffect $ P.toListM prod
      paths `shouldBe` expected
    

    and ghc tells you the type is:

    shouldReturnP2
      :: IO (Producer FilePath (SafeT IO) ()) -> [FilePath] -> IO ()
    

    and a test:

    testP2 = shouldReturnP2 (allfiles ".") ["a1.hs"]
    

    Update

    Per the discussion in the comments about putting the doesFileExist check in the pipe:

    allfiles2 :: MonadSafe m => FilePath -> Producer FilePath m ()
    allfiles2 path = do
      exists <- liftIO $ doesFileExist path
      if exists
        then each [path] >-> P.filter (".hs" `isSuffixOf`)
        else find path (glob "*.hs" <> regular)