9

In the Haskell Control.Arrow documentation it talks about Kleisli arrows' relationship to monads, but it is not obvious to me how to use this. I have a function which I think fits with arrows except for it involving the IO monad, so I think Kleisli arrows may help.

Take the following function which returns pairs of original and modified filenames of a directory.

import System.Directory
import System.FilePath

datedFiles target = do
    fns <- getDirectoryContents target
    tms <- mapM (fmap show . getModificationTime) fns
    return $ 
        zip fns $ 
        zipWith replaceBaseName fns $ 
        zipWith (++) (map takeBaseName fns) tms

If I had to draw it out, it would be something like this:

enter image description here

I think it can benefit from the use of Kleisli arrows, but I don't know how. Can anyone provide guidance?

duplode
  • 33,731
  • 7
  • 79
  • 150
Opa
  • 335
  • 2
  • 7

4 Answers4

9

Monads are Functors from Hask, the category of Haskell types and functions, to Hask---an endofunctor. That means that some of the arrows in Hask look like a -> m b for some Monad m. For a particular monad m, the subcategory of Hask where arrows look like a -> m b is the Kleisli category for m.

We know it's a category because there's an identity arrow return :: a -> m a and composition (>>>) :: (a -> m b) -> (b -> m c) -> (a -> m c) defined like

(f >>> g) a = join (g <$> f a)

which is why we need this to be a Monad---we use both return and join.


In Haskell, we can't just have a subcategory normally, but instead a newtype is used.

import Prelude hiding ((.), id)
import Control.Category

newtype Kleisli m a b = Kleisli { runKleisli :: a -> m b }

instance Monad m => Category (Kleisli m) where
  id                    = Kleisli return
  Kleisli g . Kleisli f = Kleisli (join . fmap g . f)

And then we can upgrade functions of type Monad m => a -> m b to Kleisli m a bs, arrows in a category, and compose them with (.)

arr :: Kleisli IO FilePath [String]
arr = Kleisli (mapM $ fmap show . getModificationTime) . Kleisli getDirectoryContents

Generally that's a bit syntactically noisy, though. The newtype is only valuable in order to use the Category typeclass to overload id and (.). Instead it's more likely that you'll see return and (>=>) which are equivalent to

return a = runKleisli (id a)
f >=> g  = runKleisli $ Kleisli g . Kleisli f
J. Abrahamson
  • 72,246
  • 9
  • 135
  • 180
6

datedFiles can be implemented using arrows because the information flows in a "fixed pipeline", as your diagram shows.

Here's a possible implementation that does not use map or zip on lists:

import System.Directory
import System.FilePath
import Control.Monad.List
import Control.Arrow

datedFiles :: FilePath -> IO [(FilePath,FilePath)]
datedFiles = fmap runListT . runKleisli $
   (Kleisli $ ListT . getDirectoryContents) 
   >>>
   returnA &&& ((Kleisli $ liftIO . getModificationTime) >>^ show)
   >>^
   fst &&& (\(path,time) -> replaceBaseName path $ takeBaseName path ++ time)

Arguably, it is not the most intuitive implementation.

The monad for the Kleisli arrows is ListT IO, although the only nondeterminism is caused by getDirectoryContents.

Note that the last line is a pure function; the (&&&) for the last line is using the Arrow instance for functions.

Edit: The Wrapped typeclass from the lens package can be used to add/remove newtype wrappers a bit more succinctly. Applying it to the previous example, we end up with:

import Control.Lens

datedFiles :: FilePath -> IO [(FilePath,FilePath)]
datedFiles = fmap runListT . runKleisli $
   ListT . getDirectoryContents ^. wrapped 
   >>>
   returnA &&& (liftIO . getModificationTime ^. wrapped >>^ show)
   >>^
   fst &&& (\(path,time) -> replaceBaseName path $ takeBaseName path ++ time)
danidiaz
  • 26,936
  • 4
  • 45
  • 95
3

First I'd suggest you to split handling an individual file from handling the list. In your example, timestamp is the interesting arrow, because all others are pure functions. Nevertheless, we can make some of them into arrows to make the example more interesting. Using the arrow notation we can rewrite computing one file name as a Kleisli arrow:

{-# LANGUAGE Arrows #-}
import Control.Arrow
import System.Directory
import System.FilePath
import System.Time

-- Get a timestamp of a file as an arrow:
timestamp :: Kleisli IO FilePath ClockTime
timestamp = Kleisli getModificationTime

-- Insert a given string in front of the extension of a file.
-- Just as an example - we'd rather use a simple `let` instead of making it
-- an arrow.
append :: (Monad m) => Kleisli m (FilePath, String) FilePath
append = arr $ \(fn, suffix) ->
                let (base, ext) = splitExtension fn
                in base ++ suffix ++ ext

-- Given a directory, receive the name of a file as an arrow input
-- and produce the new file name. (We could also receive `dir`
-- as an input, if we wanted.)
datedArrow :: FilePath -> Kleisli IO FilePath (FilePath, FilePath)
datedArrow dir = proc fn -> do
                    ts <- timestamp -< replaceDirectory fn dir
                    fn' <- append -< (fn, show ts)
                    returnA -< (fn, fn')

datedFiles' :: FilePath -> IO [(FilePath, FilePath)]
datedFiles' target = do
                fns <- getDirectoryContents target
                mapM (runKleisli $ datedArrow target) fns
Petr
  • 62,528
  • 13
  • 153
  • 317
1

Let remember main function from Monad:

(>>=) :: (a -> m b) -> m a  -> m b

and now let's look at Kleisli

newtype Kleisli m a b = Kleisli { runKleisli :: a -> m b }

where Kleisli is a wrapper and runKleisli - unwrapper from the newtype.

What is in common? a -> m b part

And let's look at instance declaration:

instance Monad m => Arrow (Kleisli m) where ...

we see, how to make Monad part of Arrow

wit
  • 1,612
  • 10
  • 10