问题
According to the famous paper Idioms are oblivious, arrows are meticulous, monads are promiscuous, the expressive power of arrows (without any additional typeclasses) should be somewhere strictly between applicative functors and monads: monads are equivalent to ArrowApply
, and Applicative
should be equivalent to something the paper calls "static arrows". However, it is not clear to me what restriction this "static"-ness means.
Playing around with the three typeclasses in question, I was able to build up an equivalence between applicative functors and arrows, which I present below in the context of the well-known equivalence between Monad
and ArrowApply
. Is this construction correct? (I've proven most of the arrow laws before getting bored of it). Doesn't that mean that Arrow
and Applicative
are exactly the same?
{-# LANGUAGE TupleSections, NoImplicitPrelude #-}
import Prelude (($), const, uncurry)
-- In the red corner, we have arrows, from the land of * -> * -> *
import Control.Category
import Control.Arrow hiding (Kleisli)
-- In the blue corner, we have applicative functors and monads,
-- the pride of * -> *
import Control.Applicative
import Control.Monad
-- Recall the well-known result that every monad yields an ArrowApply:
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 $ g <=< f
instance (Monad m) => Arrow (Kleisli m) where
arr = Kleisli . (return .)
first (Kleisli f) = Kleisli $ \(x, y) -> liftM (,y) (f x)
instance (Monad m) => ArrowApply (Kleisli m) where
app = Kleisli $ \(Kleisli f, x) -> f x
-- Every arrow arr can be turned into an applicative functor
-- for any choice of origin o
newtype Arrplicative arr o a = Arrplicative{ runArrplicative :: arr o a }
instance (Arrow arr) => Functor (Arrplicative arr o) where
fmap f = Arrplicative . (arr f .) . runArrplicative
instance (Arrow arr) => Applicative (Arrplicative arr o) where
pure = Arrplicative . arr . const
Arrplicative af <*> Arrplicative ax = Arrplicative $
arr (uncurry ($)) . (af &&& ax)
-- Arrplicatives over ArrowApply are monads, even
instance (ArrowApply arr) => Monad (Arrplicative arr o) where
return = pure
Arrplicative ax >>= f =
Arrplicative $ (ax >>> arr (runArrplicative . f)) &&& id >>> app
-- Every applicative functor f can be turned into an arrow??
newtype Applicarrow f a b = Applicarrow{ runApplicarrow :: f (a -> b) }
instance (Applicative f) => Category (Applicarrow f) where
id = Applicarrow $ pure id
Applicarrow g . Applicarrow f = Applicarrow $ (.) <$> g <*> f
instance (Applicative f) => Arrow (Applicarrow f) where
arr = Applicarrow . pure
first (Applicarrow f) = Applicarrow $ first <$> f
回答1:
Let's compare the IO applicative functor with the Kleisli arrows of the IO monad.
You can have an arrow that prints a value read by a previous arrow:
runKleisli ((Kleisli $ \() -> getLine) >>> Kleisli putStrLn) ()
But you can't do that with applicative functors. With applicative functors, all the effects take place before applying the function-in-the-functor to the arguments-in-the-functor. The function-in-the-functor can't use the value inside an argument-in-the-functor to "modulate" its own effect, so to speak.
回答2:
Every applicative yields an arrow and every arrow yields an applicative, but they are not equivalent. If you have an arrow arr
and a morphism arr a b
it does not follow that you can generate a morphism arr o (a \to b)
that replicates its functionality. Thus if you round trip through applicative you lose some features.
Applicatives are monoidal functors. Arrows are profunctors that are also categories, or equivalently, monoids in the category of profunctors. There is no natural connection between these two notions. If you will excuse my flippancy: In Hask it turns out that the functor part of the pro-functor in an arrow is a monoidal functor, but that construction necessarily forgets the "pro" part.
When you go from arrows to applicatives you are ignoring the part of an arrow that takes input and only using the part that deals with output. Many interesting arrows use the input part in one way or another and so by turning them into applicatives you are giving up useful stuff.
That said, in practice I find applicative the nicer abstraction to work with and one that almost always does what I want. In theory arrows are more powerfull, but I don't find my self using them in practice.
回答3:
(I've posted the below to my blog with an extended introduction)
Tom Ellis suggested thinking about a concrete example involving file I/O, so let's compare three approaches to it using the three typeclasses. To make things simple, we will only care about two operations: reading a string from a file and writing a string to a file. Files are going to be identified by their file path:
type FilePath = String
Monadic I/O
Our first I/O interface is defined as follows:
data IOM ∷ ⋆ → ⋆
instance Monad IOM
readFile ∷ FilePath → IOM String
writeFile ∷ FilePath → String → IOM ()
Using this interface, we can for example copy a file from one path to another:
copy ∷ FilePath → FilePath → IOM ()
copy from to = readFile from >>= writeFile to
However, we can do much more than that: the choice of files we manipulate can depend on effects upstream. For example, the below function takes an index file which contains a filename, and copies it to the given target directory:
copyIndirect ∷ FilePath → FilePath → IOM ()
copyIndirect index target = do
from ← readFile index
copy from (target ⟨/⟩ to)
On the flip side, this means there is no way to know upfront the set of filenames that are going to be manipulated by a given value action ∷ IOM α
. By "upfront", what I mean is the ability to write a pure function fileNames :: IOM α → [FilePath]
.
Of course, for non-IO-based monads (such as ones for which we have some kind of extractor function μ α → α
), this distinction becomes a bit more fuzzy, but it still makes sense to think about trying to extract information without evaluating the effects of the monad (so for example, we could ask "what can we know about a Reader Γ α
without having a value of type Γ
at hand?").
The reason we can't really do static analysis in this sense on monads is because the function on the right-hand side of a bind is in the space of Haskell functions, and as such, is completely opaque.
So let's try restricting our interface to just an applicative functor.
Applicative I/O
data IOF ∷ ⋆ → ⋆
instance Applicative IOF
readFile ∷ FilePath → IOF String
writeFile ∷ FilePath → String → IOF ()
Since IOF
is not a monad, there's no way to compose readFile
and writeFile
, so all we can do with this interface is to either read from a file and then postprocess its contents purely, or write to a file; but there's no way to write the contents of a file into another one.
How about changing the type of writeFile
?
writeFile′ ∷ FilePath → IOF (String → ())
The main problem with this interface is that while it would allow writing something like
copy ∷ FilePath → FilePath → IOF ()
copy from to = writeFile′ to ⟨*⟩ readFile from
it leads to all kind of nasty problems because String → ()
is such a horrible model of writing a string to a file, since it breaks referential transparency. For example, what do you expect the contents of out.txt
to be after running this program?
(λ write → [write "foo", write "bar", write "foo"]) ⟨$⟩ writeFile′ "out.txt"
Two approaches to arrowized I/O
First of all, let's get two arrow-based I/O interfaces out of the way that don't (in fact, can't) bring anything new to the table: Kleisli IOM
and Applicarrow IOF
.
The Kleisli-arrow of IOM
, modulo currying, is:
readFile ∷ Kleisli IOM FilePath String
writeFile ∷ Kleisli IOM (FilePath, String) ()
Since writeFile
's input still contains both the filename and the contents, we can still write copyIndirect
(using arrow notation for simplicity). Note how the ArrowApply
instance of Kleisli IOM
is not even used.
copyIndirect ∷ Kleisli IOM (FilePath, FilePath) ()
copyIndirect = proc (index, target) → do
from ← readFile ↢ index
s ← readFile ↢ from
writeFile ↢ (to, s)
The Applicarrow
of IOF
would be:
readFile ∷ FilePath → Applicarrow IOF () String
writeFile ∷ FilePath → String → Applicarrow IOF () ()
which of course still exhibits the same problem of being unable to compose readFile
and writeFile
.
A proper arrowized I/O interface
Instead of transforming IOM
or IOF
into an arrow, what if we start from scratch, and try to create something in between, in terms of where we use Haskell functions and where we make an arrow? Take the following interface:
data IOA ∷ ⋆ → ⋆ → ⋆
instance Arrow IOA
readFile ∷ FilePath → IOA () String
writeFile ∷ FilePath → IOA String ()
Because writeFile
takes the content from the input side of the arrow, we can still implement copy
:
copy ∷ FilePath → FilePath → IOA () ()
copy from to = readFile from >>> writeFile to
However, the other argument of writeFile
is a purely functional one, and so it can't depend on the output of e.g. readFile
; so copyIndirect
can't be implemented with this Arrow interface.
If we turn this argument around, this also means that while we can't know in advance what will end up being written to a file (before running the full IOA
pipeline itself), but we can statically determine the set of filenames that will be modified.
Conclusion
Monads are opaque to static analysis, and applicative functors are poor at expressing dynamic-time data dependencies. It turns out arrows can provide a sweet spot between the two: by choosing the purely functional and the arrowized inputs carefully, it is possible to create an interface that allows for just the right interplay of dynamic behaviour and amenability to static analysis.
来源:https://stackoverflow.com/questions/24668313/arrows-are-exactly-equivalent-to-applicative-functors