Who is afraid of arrows, was Re: [Haskell-cafe] ANNOUNCE: Haskell XML Toolbox Version 9.0.0

Gene A yumagene at gmail.com
Tue Oct 12 15:39:21 EDT 2010


>
> On Tue, Oct 12, 2010 at 8:56 AM, Uwe Schmidt <uwe at fh-wedel.de> wrote:
> >> No, but there is no point in using a formalism that adds complexity
> >> without adding functionality.  Arrows are more awkward to use than
> >> monads because they were intentionally designed to be less powerful than
> >> monads in order to cover situations in which one could not use a monad.
>

On Tue, Oct 12, 2010 at 9:49 AM, C. McCann <cam at uptoisomorphism.net> wrote

> Essentially, arrows lend themselves best to composing first-order
> computations to create larger computations with a fixed structure. If
> you find yourself forced to frequently use ArrowApply or other means
> of eliminating higher-order structure--e.g., anything that results in
> an arrow with an output type that contains fewer instances of the
> arrow's own type constructor than does the input type--it may be worth
> considering if arrows are really what you want to use.
>
> Personally, though, I think monads are really overkill in many cases
> and strongly prefer, where possible, to use Applicative or Arrow.
>
>
Well I am compelled to add my two cents worth to this conversation.  I like
to use examples, so that is what I will do.  I am going to use a simple one,
and you may wonder why I used an arrow to represent this little computation,
but the main reason is that it fits the way I think better then if's ,
guards, cases, in or where clauses.  The entirety of a computation is right
there in my face.  The other thing that I will explain after showing this
little example function {arrow under the hood} is that it leads to more
thinking of composing into even more higher orderness, until you have a
single function definition that can be the entire program.

Function splitMiddle:
     Takes a list and returns a pair consisting of the
     list split into two equal parts.

splitMiddle :: forall a. [a] -> ([a], [a])
splitMiddle  =
   (id  &&& (length >>> flip div 2)) >>>
   (\(xs,a) -> splitAt a xs)

usage:
 splitMiddle [1..10]
([1,2,3,4,5],[6,7,8,9,10])

OKAY here is where the thoughts can come in to play and are a direct
result of the pointfree style that is adopted as a direct result of using
arrow
notation.  To split the list of words of a line of text you may do this
initially:

splitMiddle $ words "Now is the time to come to the aid of our country"
(["Now","is","the","time","to","come"],["to","the","aid","of","our","country"])

Then it occurs that well hell, why not move the "words" function into the
arrow:

(words >>> splitMiddle) "Now is the time to come to the aid of our country"
(["Now","is","the","time","to","come"],["to","the","aid","of","our","country"])

That can be turned into a new function with great ease and clarity:

splitSentence :: String -> ([String], [String])
splitSentence = words >>> splitMiddle

Then maybe I decide, hey, I only want the second half of the sentence:

sndHalfSentence :: String -> [String]
sndHalfSentence = words >>> splitMiddle >>> snd

or if I have defined splitSentence as above:

sndHalfSentence :: String -> [String]
sndHalfSentence = splitSentence >>> snd

doing the function fstHalfSentence is obvious in that the mechanics
are right there to see and no variables to muck it up, just change the
snd to fst :

fstHalfSentence :: String -> [String]
fstHalfSentence = splitSentence >>> fst

The other nice use of arrow is INSIDE of a monadic structure:


 "Now is the time to come to the aid of our country" >>= (return >>> words
>>> concat)
"Nowisthetimetocometotheaidofourcountry"

which can become the definition of squeeze:

squeeze :: [Char] -> [Char]
*Big3> let squeeze cs = cs >>= (return >>> words >>> concat)

squeeze "Now is the time to come to the aid of our country"
"Nowisthetimetocometotheaidofourcountry"

and then of course you can do a few sentences instead of only
one,if you change the definition with the simple addition of an

applicative operator to the mix.

squeezeSentenceF
  :: forall (f :: * -> *). (Functor f) => f [Char] -> f [Char]
squeezeSentenceF css = (squeeze <$>) css
squeezeSentenceF ["This is how to do a list of sentences",
                              "It makes use of applicatives too"]
["Thisishowtodoalistofsentences","Itmakesuseofapplicativestoo"]

notice that this is more general then just mapping as it applies to any
functor, of which the Maybe monad has an instance..
so:
 squeezeSentenceL  (Just "This is how to do a Maybe sentence")
Just "ThisishowtodoaMaybesentence"

works just nicely.  I think that the more you mix and match ALL of the tools
and
do a little experimentation with them, that it then begins to be a situation
where
your thoughts of how to compose things are not locked down to one way and it
opens up your mind to many possibilities.  I am a proponent of having and
using
ALL the available tools in a mix and match way if need be. About the only
thing
you have to do to use any of the various tools in the same line of code is
to remember
to use a parenthetic bit of separation between one and the next.
metacode"
xss >>= ( ((g >>> h)  <$>)  >>> return)  so you are using a monadic bind to
shove something of {functor f, monad m}  embodied in xss such that f (m x)
has the
functions g and then h applied to the elements of the monad 'm'  inside of
the
functor f and then have that structure returned as:  f (m ((g>>>f) x)).

Okay, I am totally done with that.. probably just muddied things up, but
maybe
make sense if you try using ghci after loading a dummy module that imports
Control.Monad, Control.Arrow and Control.Applicative.  I just think that one
is
missing out when not using ALL the computational tools.

cheers,
gene
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20101012/7ba231b2/attachment.html


More information about the Haskell-Cafe mailing list