3

I have the following module which implements a directory walk:

module Walk
  ( walk
  ) where

import           Control.Monad
import           Control.Monad.IO.Class
import           Data.List
import           System.Directory
import           System.FilePath

walk :: (MonadIO m) => FilePath -> m [(FilePath, [FilePath])]
walk root = do
  entries <- liftIO $ listDirectory root
  (files, dirs) <- partition snd <$> liftM2 (<$>) zip (mapM (liftIO . doesFileExist . (root </>))) entries
  ((root, map fst files) :) . concat <$> mapM (walk . (root </>) . fst) dirs

It currently returns a list, but I'd like it to return a Traversable instead:

walk :: (MonadIO m, Traversable t) => FilePath -> m (t (FilePath, [FilePath]))

If I change the signature, I get the following error:

    • Couldn't match type ‘t’ with ‘[]’
      ‘t’ is a rigid type variable bound by
        the type signature for:
          walk :: forall (m :: * -> *) (t :: * -> *).
                  (MonadIO m, Traversable t) =>
                  FilePath -> m (t (FilePath, [FilePath]))
      Expected type: m (t (FilePath, [FilePath]))
        Actual type: m [(FilePath, [FilePath])]
    • In a stmt of a 'do' block:
        ((root, map fst files) :) . concat
          <$> mapM (walk . (root </>) . fst) dirs
      In the expression:
        do entries <- liftIO $ listDirectory root
           (files, dirs) <- partition snd
                              <$>
                                liftM2
                                  (<$>) zip (mapM (liftIO . doesFileExist .
(root </>))) entries
           ((root, map fst files) :) . concat
             <$> mapM (walk . (root </>) . fst) dirs
      In an equation for ‘walk’:
          walk root
            = do entries <- liftIO $ listDirectory root
                 (files, dirs) <- partition snd
                                    <$>
                                      liftM2
                                        (<$>)
                                        zip
                                        (mapM (liftIO . doesFileExist .
(root </>)))
                                        entries
                 ((root, map fst files) :) . concat
                   <$> mapM (walk . (root </>) . fst) dirs
    • Relevant bindings include
        walk :: FilePath -> m (t (FilePath, [FilePath]))

I think it's failing on the :? I can't be sure. How do I fix this?

Listerone
  • 1,381
  • 1
  • 11
  • 25
  • What would you use the generalised version for? I'm inclined to think it would be enough to have `walk` return a specific structure (be it a list, a map, or something else) and then convert it into something else in a separate step, but it might help to know your intended use case. – duplode Jun 01 '19 at 15:35

2 Answers2

5

I think it's failing on the :?

Indeed it is. If you use (:) to build the structure, the structure will be a list, and you can't change the type of walk to claim it returns an arbitrary traversable structure. There isn't really a good Traversable-centric workaround, either: Traversable means you have, via its Foldable superclass, a toList, but not a fromList.

duplode
  • 33,731
  • 7
  • 79
  • 150
  • 2
    Exactly. This can be determined by looking at the type signatures of the Traversable methods. All of them have the traversable `t` in the negative position and thus can not be used to product an arbitrary `t` result. – Thomas M. DuBuisson Jun 01 '19 at 15:39
3

Polymorphic production of lists, and designing classes for polymorphic containers in general, has proven to be more difficult than it might first appear. GHC's current solution for producing fully polymorphic containers, vs just operating over a pre-existing container such as with Traversable, is the IsList class.

Defined in GHC.Exts as:

class IsList l where
  type Item l
  fromList  :: [Item l] -> l
  ...

There are already instances for lists, non empty lists, maps, and most other types coming from what you'd think of as standard Haskell libraries.

Notice the type parameter, l, is of kind * and not what you might expect from a container of * -> *. You provide the fully applied type and can constrain the Item l type with type equality if desired. For example:

{-# LANGUAGE TypeFamilies #-}
module Walk
  ( walk
  ) where

import           Control.Monad
import           Control.Monad.IO.Class
import           Data.List
import           System.Directory
import           System.FilePath
import           GHC.Exts

walk :: (IsList l, Item l ~ (FilePath,[FilePath]), MonadIO m) => FilePath -> m l
walk root =
  do entries <- liftIO $ listDirectory root
     (files, dirs) <- partition snd <$> liftM2 (<$>) zip (mapM (liftIO . doesFileExist . (root </>))) entries
     fromList . ((root, map fst files) :) . concat <$> mapM (walk . (root </>) . fst) dirs
Thomas M. DuBuisson
  • 64,245
  • 7
  • 109
  • 166