
On 02/08/10 18:44, Henning Thielemann wrote:
On Mon, 2 Aug 2010, David Menendez wrote:
On Sun, Aug 1, 2010 at 9:52 AM, Maciej Marcin Piechotka
wrote: The proposal is to add (<.>) function to Data.Functor/Control.Applicative: (<.>) :: (b -> c) -> (a -> f b) -> a -> f c f <.> g = fmap f . g -- (<.>) = (.) . fmap
In intend it is related to <$> in the same way as (.) is related to $: (a . b . c) d = a $ b $ c $ d (a <.> b <.> c) d = a <$> b <$> c <$> d
I'm not convinced. "fmap f . g" isn't that much longer than "f <.> g" and requires no new combinators.
'f' and 'g' might be infix expressions. Depending on the precedence we had to compare "fmap (f) . g" with "f <.> g" or "fmap (f) . (g)" with "f <.> g" .
Well - even for other expressions (not necessary infix: fmap (div 5) . read vs div 5 <.> read fmap (f . g) . h vs. f . g <.> h
I'd argue that "fmap f . fmap g . h" is better style, since it's obvious that this should be rewritten as "fmap (f . g) . h". In the example above, "a <$> b <$> c <$> d" is best transformed to "a . b . c <$> d".
I am also happy with
fmap f . fmap g . h
and
a . b . c <$> d
.
The "a <$> b <$> c <$> d" was done to show the relation between $/. and <$>/<.>. Some random usage in my files:
in Reactive e s a' (accumR' a' <.> n) r
= Reactive ef (sf <> ev <> sv) v ((`filterR` rv) <.> nf) (ff *> fv)
f `fmap` Behavior b = Behavior $ fmap f <.> b
accumB b = Behavior $ accumR <.> unBeh b
show = unsafePerformIO . (decode <.> peekArray0 0 <=< toString)
lookupQuark = guardQuark <.> flip (withArray0 0) tryString . encode
peek = Boolean . ((==0) :: GBoolean -> Bool) <.> peek . castPtr
show = unsafePerformIO . (decode <.> peekArray0 0 <=< typeName
typeFromName = typeCheck <.> flip (withArray0 0) fromName . encode
typeAncestors = unfoldr ((id &&& id) <.> typeParent)
vs.
in Reactive e s a' (fmap (accumR' a') . n) r
= Reactive ef (sf <> ev <> sv) v (fmap (`filterR` rv) . nf) (ff *> fv)
f `fmap` Behavior b = Behavior $ fmap (fmap f) . b
accumB b = Behavior $ fmap accumR . unBeh b
show = unsafePerformIO . (fmap decode . peekArray0 0 <=< toString
lookupQuark = fmap guardQuark . flip (withArray0 0) tryString . encode
peek = fmap (Boolean . ((==0) :: GBoolean -> Bool)) . peek . castPtr
show = unsafePerformIO . (fmap decode . peekArray0 0 <=< typeName)
typeFromName = fmap typeCheck . flip (withArray0 0) fromName . encode
typeAncestors = unfoldr (fmap (id &&& id) . typeParent)
Regards