Looking for pointfree version

Hi, Is there a nice way to write down :: Focus -> [Focus] down p = concat [downPar p, downNew p, downTrans p] in point-free style? (In doesn't make much difference what these functions do; if it helps, their types are downPar, downNew, downTrans :: Focus -> [Focus]). Ideally, I would like to write something like down = downPar ... downNew ... downTrans but I'm not sure what should be on the dots. This works: down = concat . flip map [downPar, downNew, downTrans] . flip ($) but is extremely ugly and doesn't really explain what's going on :) (It seems to me I should be able to take advantage of the list monad, somehow). Pointers appreciated! Edsko

On Mon, 9 Feb 2009 14:18:18 +0000
Edsko de Vries
Hi,
Is there a nice way to write
down :: Focus -> [Focus] down p = concat [downPar p, downNew p, downTrans p]
in point-free style?
I think this should work: down = concat . swing map [downPar, downNew, downTrans] swing is defined at http://www.haskell.org/haskellwiki/Pointfree#Swing -- Robin

On the same note, does anyone have ideas for the following snippet? Tried the pointfree package but the output was useless. pointwise op (x0,y0) (x1,y1) = (x0 `op` x1, y0 `op` y1) Edsko de Vries wrote:
Perfect! Beautiful. I was hoping there'd be a simple solution like that.
Thanks!
On 9 Feb 2009, at 14:31, Wouter Swierstra wrote:
How about using Data.Monoid:
down = downPar `mappend` downNew `mappend` downTrans
-- View this message in context: http://www.nabble.com/Looking-for-pointfree-version-tp21913653p21971304.html Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

On Thu, Feb 12, 2009 at 8:46 AM, Kim-Ee Yeoh
On the same note, does anyone have ideas for the following snippet? Tried the pointfree package but the output was useless.
pointwise op (x0,y0) (x1,y1) = (x0 `op` x1, y0 `op` y1)
import Control.Monad.Reader -- for the (Monad (a ->)) instance import Control.Bifunctor -- package category-extras dup = join (,) mapPair = uncurry bimap pointfree = (mapPair .) . mapPair . dup Or if you're not afraid of *some* points, and want to avoid the imports: dup x = (x,x) mapPair (f,g) (x,y) = (f x, g y) pointfree op = mapPair . mapPair (dup op) That what you're looking for? :-) - Benja

Benja Fallenstein wrote:
Kim-Ee Yeoh wrote:
On the same note, does anyone have ideas for the following snippet? Tried the pointfree package but the output was useless.
pointwise op (x0,y0) (x1,y1) = (x0 `op` x1, y0 `op` y1)
import Control.Monad.Reader -- for the (Monad (a ->)) instance import Control.Bifunctor -- package category-extras
dup = join (,) mapPair = uncurry bimap pointfree = (mapPair .) . mapPair . dup
Or if you're not afraid of *some* points, and want to avoid the imports:
dup x = (x,x) mapPair (f,g) (x,y) = (f x, g y) pointfree op = mapPair . mapPair (dup op)
That what you're looking for? :-)
The pairs are of course an applicative functor (<*>) = uncurry (***) -- from Control.Arrow pure x = (x,x) pointwise op x y = pure op <*> x <*> y Regards, apfelmus -- http://apfelmus.nfshost.com

On Thu, 2009-02-12 at 11:08 +0100, Heinrich Apfelmus wrote:
Benja Fallenstein wrote:
Kim-Ee Yeoh wrote:
On the same note, does anyone have ideas for the following snippet? Tried the pointfree package but the output was useless.
pointwise op (x0,y0) (x1,y1) = (x0 `op` x1, y0 `op` y1)
import Control.Monad.Reader -- for the (Monad (a ->)) instance import Control.Bifunctor -- package category-extras
dup = join (,) mapPair = uncurry bimap pointfree = (mapPair .) . mapPair . dup
Or if you're not afraid of *some* points, and want to avoid the imports:
dup x = (x,x) mapPair (f,g) (x,y) = (f x, g y) pointfree op = mapPair . mapPair (dup op)
That what you're looking for? :-)
The pairs are of course an applicative functor
(<*>) = uncurry (***) -- from Control.Arrow pure x = (x,x)
pointwise op x y = pure op <*> x <*> y
Regards, apfelmus
Concretely (this might do with a few laziness notations):
import Control.Applicative
data Pair a = a :*: a
instance Functor Pair where f `fmap` (x :*: y) = f x :*: f y
instance Applicative Pair where (f :*: g) <*> (x :*: y) = f x :*: f y pure x = x :*: x
pointfree :: (a -> b -> c) -> Pair a -> Pair b -> Pair c --pointfree o x y = pure o <*> x <*> y pointfree = ((<*>) .) . (<*>) . pure -- in the applicative paper notation: --pointfree o x y = [| o x y |]

import Control.Applicative
data Pair a = a :*: a
instance Functor Pair where f `fmap` (x :*: y) = f x :*: f y
instance Applicative Pair where (f :*: g) <*> (x :*: y) = f x :*: f y
The last f needs to be a g.
pure x = x :*: x
pointfree :: (a -> b -> c) -> Pair a -> Pair b -> Pair c --pointfree o x y = pure o <*> x <*> y pointfree = ((<*>) .) . (<*>) . pure -- in the applicative paper notation: --pointfree o x y = [| o x y |]
Very nice. Aside: I wonder how much work it would be to extend the pointfree tool to infer such equalities? -- View this message in context: http://www.nabble.com/Looking-for-pointfree-version-tp21913653p22027350.html Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

On Thu, Feb 12, 2009 at 6:46 PM, Kim-Ee Yeoh
On the same note, does anyone have ideas for the following snippet? Tried the pointfree package but the output was useless.
pointwise op (x0,y0) (x1,y1) = (x0 `op` x1, y0 `op` y1)
$ pointfree '(\op (a, b) (c, d) -> (a `op` c, b `op` d))' (`ap` snd) . (. fst) . flip flip snd . ((flip . (ap .)) .) . flip flip fst . ((flip . ((.) .)) .) . (flip =<< (((.) . flip . (((.) . (,)) .)) .)) 'Useless' is a bit understated , IMO.

And then to
down = mconcat [downPar, downNew, downTrans]
Which is pretty cute considering that the original formulation is equivalent
to and a tiny tweak away from
down p = mconcat [downPar p, downNew p, downTrans p]
Hooray for Monoid!
- Conal
On Mon, Feb 9, 2009 at 6:31 AM, Wouter Swierstra
snip
How about using Data.Monoid:
down = downPar `mappend` downNew `mappend` downTrans
Wouter
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Rewriting it to: concatMap ($ p)[downPar , downNew , downTrans ] gives: ($ p) =<< [downPar, downNew, downTrans] didn't check though! =@@i Edsko de Vries schreef:
Hi,
Is there a nice way to write
down :: Focus -> [Focus] down p = concat [downPar p, downNew p, downTrans p]
in point-free style? (In doesn't make much difference what these functions do; if it helps, their types are downPar, downNew, downTrans :: Focus -> [Focus]).
Ideally, I would like to write something like
down = downPar ... downNew ... downTrans
but I'm not sure what should be on the dots. This works:
down = concat . flip map [downPar, downNew, downTrans] . flip ($)
but is extremely ugly and doesn't really explain what's going on :) (It seems to me I should be able to take advantage of the list monad, somehow).
Pointers appreciated!
Edsko
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (11)
-
Aai
-
Benja Fallenstein
-
Conal Elliott
-
Edsko de Vries
-
George Pollard
-
Heinrich Apfelmus
-
Henning Thielemann
-
Kim-Ee Yeoh
-
Robin Green
-
Toby Hutton
-
Wouter Swierstra